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

commits at source.squeak.org commits at source.squeak.org
Wed Apr 22 17:03:39 UTC 2015


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

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

Name: VMMaker.oscog-eem.1237
Author: eem
Time: 22 April 2015, 10:00:33.801 am
UUID: 0864d0ce-8b0f-4415-ab43-13e2581488d5
Ancestors: VMMaker.oscog-cb.1236

Change source file output for the Cogit so that
cogit.c includes cogitARMv5.c or cogitIA32.c as
appropriate, using the same style as
ThreadedFFIPlugin.

Fix some generation-time errors and warnings for
ARM.

=============== Diff against VMMaker.oscog-cb.1236 ===============

Item was changed:
  ----- Method: CCodeGenerator>>generateMinus:on:indent: (in category 'C translation') -----
  generateMinus: msgNode on: aStream indent: level
  	"Generate the C code for this message onto the given stream."
  
  	(self generateAsConstantExpression: msgNode on: aStream) ifFalse:
+ 		[msgNode args first constantNumbericValueOrNil ifNotNil:
+ 			[:value|
+ 			 value = 0 ifTrue:
+ 				[^self emitCExpression: msgNode receiver on: aStream]].
+ 		 self emitCExpression: msgNode receiver on: aStream.
- 		[self emitCExpression: msgNode receiver on: aStream.
  		 aStream nextPutAll: ' - '.
  		 self emitCExpression: msgNode args first on: aStream]!

Item was changed:
  ----- Method: CCodeGenerator>>generatePlus:on:indent: (in category 'C translation') -----
  generatePlus: msgNode on: aStream indent: level
  	"Generate the C code for this message onto the given stream."
  	(self generateAsConstantExpression: msgNode on: aStream) ifFalse:
+ 		[msgNode args first constantNumbericValueOrNil ifNotNil:
+ 			[:value|
+ 			 value = 0 ifTrue:
+ 				[^self emitCExpression: msgNode receiver on: aStream]].
+ 		 self emitCExpression: msgNode receiver on: aStream.
- 		[self emitCExpression: msgNode receiver on: aStream.
  		 aStream nextPutAll: ' + '.
  		 self emitCExpression: msgNode args first on: aStream]!

Item was changed:
  ----- Method: CCodeGenerator>>generateTimes:on:indent: (in category 'C translation') -----
  generateTimes: msgNode on: aStream indent: level
  	"Generate the C code for this message onto the given stream."
  
  	(self generateAsConstantExpression: msgNode on: aStream) ifFalse:
+ 		[msgNode args first constantNumbericValueOrNil ifNotNil:
+ 			[:value|
+ 			 value = 0 ifTrue:
+ 				[^self emitCExpression: msgNode args first on: aStream].
+ 			 value = 1 ifTrue:
+ 				[^self emitCExpression: msgNode receiver on: aStream]].
+ 		 self emitCExpression: msgNode receiver on: aStream.
- 		[self emitCExpression: msgNode receiver on: aStream.
  		 aStream nextPutAll: ' * '.
  		 self emitCExpression: msgNode args first on: aStream]!

Item was changed:
  CogAbstractInstruction subclass: #CogARMCompiler
+ 	instanceVariableNames: 'conditionOrNil'
- 	instanceVariableNames: 'cond'
  	classVariableNames: 'AL AddOpcode AndOpcode BICCqR BicOpcode CArg0Reg CArg1Reg CArg2Reg CArg3Reg CC CPSRReg CS CmpOpcode ConcreteIPReg ConcreteVarBaseReg EQ GE GT HI LDMFD LE LR LS LT MI MRS MSR MoveNotOpcode MoveOpcode NE OrOpcode OverflowFlag PC PL R0 R1 R10 R11 R12 R2 R3 R4 R5 R6 R7 R8 R9 RsbOpcode SMLALOpcode SMULL SP STMFD SubOpcode VC VS XorOpcode'
  	poolDictionaries: ''
  	category: 'VMMaker-JIT'!
  
  !CogARMCompiler commentStamp: 'lw 8/23/2012 19:38' prior: 0!
  I generate ARM instructions from CogAbstractInstructions.  For reference see
  http://infocenter.arm.com/help/index.jsp?topic=/com.arm.doc.set.architecture/index.html
  
  The Architecture Reference Manual used is that of version 5, which includes some version 6 instructions. Of those, only pld is used(for PrefetchAw).
  
  This class does not take any special action to flush the instruction cache on instruction-modification.!

Item was added:
+ ----- Method: CogARMCompiler class>>ISA (in category 'translation') -----
+ ISA
+ 	"Answer the name of the ISA the receiver implements."
+ 	^#ARMv5!

Item was changed:
  ----- Method: CogARMCompiler class>>filteredInstVarNames (in category 'translation') -----
  filteredInstVarNames
+ 	"Edit such that conditionOrNil is amongst the char size vars opcode machineCodeSize and maxSize."
+ 	^(super filteredInstVarNames copyWithout: 'conditionOrNil')
+ 		copyReplaceFrom: 4 to: 3 with: #('conditionOrNil')!
- 	"Edit such that cond is amongst the char size vars opcode machineCodeSize and maxSize."
- 	^(super filteredInstVarNames copyWithout: 'cond')
- 		copyReplaceFrom: 4 to: 3 with: #('cond')!

Item was added:
+ ----- Method: CogARMCompiler class>>identifyingPredefinedMacros (in category 'translation') -----
+ identifyingPredefinedMacros
+ 	^#('__ARM_ARCH__' '__arm__' '__arm32__' 'ARM32')!

Item was changed:
  ----- Method: CogARMCompiler>>concretizeAddCqR (in category 'generate machine code - concretize') -----
  concretizeAddCqR
  	"Will get inlined into concretizeAt: switch."
  	"Try whether the quick constant is a small negative number. If it is, optimize."
  	<inline: true>
  	self rotateable8bitImmediate: (operands at: 0)
  		ifTrue: [ :rot :immediate | | reg |
  			reg := self concreteRegister: (operands at: 1).
  			self machineCodeAt: 0 put: (self adds: reg rn: reg imm: immediate ror: rot).
  			^machineCodeSize := 4]
  		ifFalse: [
  			self rotateable8bitImmediate: (operands at: 0) negated
  				ifTrue: [ :rot :immediate | |reg|
  					reg := self concreteRegister: (operands at: 1).
  					self machineCodeAt: 0 put: (self subs: reg rn: reg imm: immediate ror: rot).
  					^machineCodeSize := 4]
+ 				ifFalse: [^self concretizeDataOperationCwR: 4]].
+ 	^0 "to keep Slang happy"!
- 				ifFalse: [^self concretizeDataOperationCwR: 4]]!

Item was changed:
  ----- Method: CogARMCompiler>>concretizeAndCqR (in category 'generate machine code - concretize') -----
  concretizeAndCqR
  	"Will get inlined into concretizeAt: switch."
  	"AND is very important since it's used to mask all sorts of flags in the jit. We take special care to try to find fast ways to make the masks"
  	<inline: true>
  	|val|
  	val := operands at: 0.
  	self rotateable8bitImmediate: val
  		ifTrue: [ :rot :immediate | | reg |
  			reg := self concreteRegister: (operands at: 1).
  			self machineCodeAt: 0 put: (self ands: reg rn: reg imm: immediate ror: rot).
  			^machineCodeSize := 4]
  		ifFalse: [
  			"see if the constant bit-inverted makes a quick value and if so BIC it instead
  			If the value is -ve, we 2s complement it instead"
  			|invVal|
  			val <0
  				ifTrue:[invVal := -1 - val]
  				ifFalse:[invVal := val bitInvert32].
  			self rotateable8bitImmediate: invVal
  				ifTrue: [ :rot :immediate | |reg|
  					reg := self concreteRegister: (operands at: 1).
  					self machineCodeAt: 0 put: (self bics: reg rn: reg imm: immediate ror: rot).
  					^machineCodeSize := 4]
  				ifFalse: ["let's try to see if the constant can be made from a simple shift of 0xFFFFFFFF"
  					|hb reg|
  					reg := self concreteRegister: (operands at: 1).
  					hb := (operands at: 0) highBit.
  					1 << hb = (val +1)
  						ifTrue: [ "MVN temp reg, 0, making 0xffffffff"
  							self machineCodeAt: 0 put:(self mvn: ConcreteIPReg imm: 0 ror: 0).
  							"Then AND reg, temp reg, lsr #(32-hb)"
  							 self machineCodeAt: 4 put:(self dataOpType: AndOpcode rd: reg rn: reg rm: ConcreteIPReg lsr: (32-hb )).
  							^machineCodeSize :=8]
+ 						ifFalse: [^self concretizeDataOperationCwR: AndOpcode]]].
+ 	^0 "to keep Slang happy"!
- 						ifFalse: [^self concretizeDataOperationCwR: AndOpcode]]]!

Item was changed:
  ----- Method: CogARMCompiler>>concretizeAndCqRR (in category 'generate machine code - concretize') -----
  concretizeAndCqRR
  	"Will get inlined into concretizeAt: switch."
  	"AND is very important since it's used to mask all sorts of flags in the jit. We take special care to try to find fast ways to make the masks"
  	<inline: true>
  	| val srcReg dstReg |
  	val := operands at: 0.
  	srcReg := self concreteRegister: (operands at: 1).
  	dstReg := self concreteRegister: (operands at: 2).
  	self rotateable8bitImmediate: val
  		ifTrue:
  			[ :rot :immediate |
  			self machineCodeAt: 0 put: (self ands: dstReg rn: srcReg imm: immediate ror: rot).
  			^machineCodeSize := 4]
  		ifFalse:
  			["see if the constant bit-inverted makes a quick value and if so BIC it instead
  			If the value is -ve, we 2s complement it instead"
  			|invVal|
  			invVal := val < 0
  						ifTrue:[-1 - val]
  						ifFalse:[val bitInvert32].
  			self rotateable8bitImmediate: invVal
  				ifTrue:
  					[ :rot :immediate |
  					self machineCodeAt: 0 put: (self bics: dstReg rn: srcReg imm: immediate ror: rot).
  					^machineCodeSize := 4]
  				ifFalse: "let's try to see if the constant can be made from a simple shift of 0xFFFFFFFF"
  					[| hb |
  					hb := (operands at: 0) highBit.
  					1 << hb = (val +1)
  						ifTrue: "MVN temp reg, 0, making 0xffffffff"
  							[self machineCodeAt: 0 put:(self mvn: ConcreteIPReg imm: 0 ror: 0).
  							"Then AND reg, temp reg, lsr #(32-hb)"
  							 self machineCodeAt: 4 put: (self dataOpType: AndOpcode rd: dstReg rn: srcReg rm: ConcreteIPReg lsr: 32 - hb).
  							^machineCodeSize := 8]
  						ifFalse:
+ 							[^self concretizeDataOperationCwR: AndOpcode]]].
+ 	^0 "to keep Slang happy"!
- 							[^self concretizeDataOperationCwR: AndOpcode]]]!

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: conditionOrNil notNil.
+ 	savedCond := conditionOrNil.
+ 	conditionOrNil := nil.
- 	self assert: cond notNil.
- 	savedCond := cond.
- 	cond := nil.
  	self dispatchConcretize.
+ 	conditionOrNil := savedCond.
- 	cond := savedCond.
  	0 to: machineCodeSize-1 by: 4 do:
  		[:i| | instr |
  		instr := (self machineCodeAt: i) bitClear: 16rF<<28.
+ 		self machineCodeAt: i put: (instr bitOr: (conditionOrNil bitAnd: 16rF)<<28)]!
- 		self machineCodeAt: i put: (instr bitOr: (cond bitAnd: 16rF)<<28)]!

Item was changed:
  ----- Method: CogARMCompiler>>concretizeDataOperationCqR: (in category 'generate machine code - concretize') -----
  concretizeDataOperationCqR: armOpcode
  	"Will get inlined into concretizeAt: switch."
  	"4 == Add, 2 == Sub, Xor == 1, And == 0, Or == 12, Bic == 14"
  	<inline: true>
  	|val rd rn |
  	val := operands at: 0.
  	rn := self concreteRegister: (operands at: 1).
  	rd := opcode = CmpOpcode ifTrue: [0] ifFalse:[rn].
  
  	self  rotateable8bitImmediate: val 
  		ifTrue: [:rot :immediate |
  			self machineCodeAt: 0 put: (self type: 1 op: armOpcode set: 1 rn: rn rd: rd shifterOperand: ((rot>>1)"in this usage we have to halve the rot value" << 8 bitOr: immediate)).
  			^machineCodeSize := 4]
  		ifFalse: ["let's try to see if the constant can be made from a simple shift of 0xFFFFFFFF"
  				val > 0 ifTrue: [
  					|hb |
  					hb := val highBit.
  					1 << hb = (val +1)
  						ifTrue: [ "MVN temp,  #0, making 0xffffffff"
  							self machineCodeAt: 0 put:(self mvn: ConcreteIPReg imm: 0 ror: 0).
  							"Then armOpcode reg, temp reg, lsr #(32-hb)"
  							 self machineCodeAt: 4 put:(self dataOpType: armOpcode rd: rd  rn: rn rm: ConcreteIPReg lsr: (32-hb)).
  							^machineCodeSize :=8]].
  					^self concretizeDataOperationCwR: armOpcode].
+ 	^0 "to keep Slang happy"
  	!

Item was changed:
  ----- Method: CogARMCompiler>>concretizeLoadEffectiveAddressMwrR (in category 'generate machine code - concretize') -----
  concretizeLoadEffectiveAddressMwrR
  	"Will get inlined into concretizeAt: switch."
  	"destReg = srcReg (which contains an address) + offset"
  	<inline: true>
  	| srcReg offset destReg instrOffset |
  	offset := operands at: 0.
  	srcReg := self concreteRegister: (operands at: 1).
  	destReg := self concreteRegister: (operands at: 2).
  	self rotateable8bitImmediate: offset
  		ifTrue:
  			[ :rot :immediate | 
  			self machineCodeAt: 0 
  				"add destReg, srcReg, #immediate ROR rot"
  				put: (self add: destReg rn: srcReg imm: immediate ror: rot<<1).
+ 			machineCodeSize := 4]
- 			^machineCodeSize := 4]
  		ifFalse:
  			[instrOffset := self at: 0 moveCw: offset intoR: ConcreteIPReg.
  			"add destReg, srcReg, ConcreteIPReg"
  			self machineCodeAt: 16 put: (self add: destReg rn: srcReg rm: ConcreteIPReg).
+ 			machineCodeSize := instrOffset + 4].
+ 	^machineCodeSize "to keep Slang happy"!
- 			^machineCodeSize := instrOffset + 4 ]!

Item was changed:
  ----- Method: CogARMCompiler>>concretizeMoveCqR (in category 'generate machine code - concretize') -----
  concretizeMoveCqR
  	"Will get inlined into concretizeAt: switch."
  	"If the quick constant is in fact a shiftable 8bit, generate the apropriate MOV, otherwise do what is necessary for a whole word."
  	<inline: true>
  	|word reg|
  	word := operands at: 0.
  	reg := self concreteRegister: (operands at: 1).
  	self 
  		rotateable8bitImmediate: (operands at: 0) 
  		ifTrue: [:rot :immediate |
  			self machineCodeAt: 0 put: (self mov: reg imm: immediate ror: rot).
  			^machineCodeSize := 4]
  		ifFalse: [|invVal|
  			word <0
  				ifTrue:[invVal := -1 - word]
  				ifFalse:[invVal := word bitInvert32].
  			self rotateable8bitImmediate: invVal
  				ifTrue: [ :rot :immediate |
  					self machineCodeAt: 0 put: (self mvn: reg imm: immediate ror: rot).
  					^machineCodeSize := 4]
+ 				ifFalse: [^self concretizeMoveCwR]].
+ 	^0 "to keep Slang happy"!
- 				ifFalse: [^self concretizeMoveCwR]]
- 	!

Item was changed:
  ----- Method: CogARMCompiler>>concretizeMoveM16rR (in category 'generate machine code - concretize') -----
  concretizeMoveM16rR
  	"Will get inlined into concretizeAt: switch."
  	"ldrh destReg, [srcReg, #immediate],
  	or 
  	move offset to ConcreteIPReg
  	ldrh destReg, [srcReg, ConcreteIPReg]"
  	<inline: true>
  	| srcReg offset destReg instrOffset|
  	offset := operands at: 0.
  	srcReg := self concreteRegister: (operands at: 1).
  	destReg := self concreteRegister: (operands at: 2).
  	self is8BitValue: offset
  		ifTrue:
  			[ :u :immediate | 
  			self machineCodeAt: 0 "ldrh destReg, [srcReg, #immediate]"
  				put: (self ldrh: destReg rn: srcReg plus: u imm: immediate).
  			^machineCodeSize := 4]
  		ifFalse:
  			[instrOffset := self at: 0 moveCw: offset intoR: ConcreteIPReg.
  			"ldrh destReg, [srcReg, ConcreteIPReg]"
  			self machineCodeAt: instrOffset put: (self ldrh: destReg rn: srcReg rm: ConcreteIPReg).
+ 			^machineCodeSize := instrOffset + 4 ].
+ 	^0 "to keep Slang happy"!
- 			^machineCodeSize := instrOffset + 4 ]!

Item was changed:
  ----- Method: CogARMCompiler>>concretizeMoveMbrR (in category 'generate machine code - concretize') -----
  concretizeMoveMbrR
  	"Will get inlined into concretizeAt: switch."
  	"ldrb destReg, [srcReg, #immediate] or ldrb destReg, [srcReg, ConcreteIPReg]"
  	<inline: true>
  	| srcReg offset destReg instrOffset|
  	offset := operands at: 0.
  	srcReg := self concreteRegister: (operands at: 1).
  	destReg := self concreteRegister: (operands at: 2).
  	self is12BitValue: offset
  		ifTrue:
  			[ :u :immediate | 
  			self machineCodeAt: 0 "ldrb destReg, [srcReg, #immediate]"
  				put: (self ldrb: destReg rn: srcReg plus: u imm: immediate).
  			^machineCodeSize := 4]
  		ifFalse:
  			[(self isAddressRelativeToVarBase: offset)
  				ifTrue:
  					[self machineCodeAt: 0 put: (self adds: ConcreteIPReg rn: ConcreteVarBaseReg imm: offset - cogit varBaseAddress ror: 0).
  					 instrOffset := 4]
  				ifFalse:
  					[instrOffset := self at: 0 moveCw: offset intoR: ConcreteIPReg].
  			 "ldrb destReg, [srcReg, ConcreteIPReg]"
  			 self machineCodeAt: instrOffset put: (self ldrb: destReg rn: srcReg rm: ConcreteIPReg).
+ 			 ^machineCodeSize := instrOffset + 4].
+ 	^0 "to keep Slang happy"!
- 			 ^machineCodeSize := instrOffset + 4]!

Item was changed:
  ----- Method: CogARMCompiler>>concretizeMoveMwrR (in category 'generate machine code - concretize') -----
  concretizeMoveMwrR
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| srcReg offset destReg instrOffset|
  	offset := operands at: 0.
  	srcReg := self concreteRegister: (operands at: 1).
  	destReg := self concreteRegister: (operands at: 2).
  	self is12BitValue: offset
  		ifTrue:
  			[ :u :immediate | 
  			self machineCodeAt: 0 "ldr destReg, [srcReg, #immediate]"
  				put: (self ldr: destReg rn: srcReg plus: u imm: immediate).
  			^machineCodeSize := 4]
  		ifFalse:
  			[instrOffset := self at: 0 moveCw: offset intoR: ConcreteIPReg.
  			"ldr destReg, [srcReg, ConcreteIPReg]"
  			self machineCodeAt: instrOffset put: (self ldr: destReg rn: srcReg rm: ConcreteIPReg).
+ 			^machineCodeSize := instrOffset + 4].
+ 	^0 "to keep Slang happy"!
- 			^machineCodeSize := instrOffset + 4]!

Item was changed:
  ----- Method: CogARMCompiler>>concretizeMoveRMbr (in category 'generate machine code - concretize') -----
  concretizeMoveRMbr
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| srcReg offset baseReg instrOffset|
  	srcReg := self concreteRegister: (operands at: 0).
  	offset := operands at: 1.
  	baseReg := self concreteRegister: (operands at: 2).
  	self is12BitValue: offset
  		ifTrue:
  			[ :u :immediate | 
  			self machineCodeAt: 0 "strb 	srcReg, [baseReg, #immediate]"
  				put: (self strb: srcReg rn: baseReg plus: u imm: immediate).
  			^machineCodeSize := 4]
  		ifFalse:
  			[(self isAddressRelativeToVarBase: offset)
  				ifTrue:
  					[self machineCodeAt: 0 put: (self adds: ConcreteIPReg rn: ConcreteVarBaseReg imm: offset - cogit varBaseAddress ror: 0).
  					 instrOffset := 4]
  				ifFalse:
  					[instrOffset := self at: 0 moveCw: offset intoR: ConcreteIPReg].
  			"strb 	srcReg, [baseReg, ConcreteIPReg]"
  			self machineCodeAt: instrOffset put: (self strb: srcReg rn: baseReg rm: ConcreteIPReg).
+ 			^machineCodeSize := instrOffset + 4 ].
+ 	^0 "to keep Slang happy"!
- 			^machineCodeSize := instrOffset + 4 ]!

Item was changed:
  ----- Method: CogARMCompiler>>concretizeMoveRMwr (in category 'generate machine code - concretize') -----
  concretizeMoveRMwr
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| srcReg offset baseReg instrOffset|
  	srcReg := self concreteRegister: (operands at: 0).
  	offset := operands at: 1.
  	baseReg := self concreteRegister: (operands at: 2).
  	self is12BitValue: offset
  		ifTrue:
  			[ :u :immediate | 
  			self machineCodeAt: 0  "str 	srcReg, [baseReg, #immediate]"
  				put: (self str: srcReg rn: baseReg plus: u imm: immediate).
  			^machineCodeSize := 4]
  		ifFalse:
  			[instrOffset := self at: 0 moveCw: offset intoR: ConcreteIPReg.
  			"str srcReg, [baseReg, ConcreteIPReg]"
  			self machineCodeAt: instrOffset put: (self str: srcReg rn: baseReg rm: ConcreteIPReg).
+ 			^machineCodeSize := instrOffset + 4].
+ 	^0 "to keep Slang happy"!
- 			^machineCodeSize := instrOffset + 4]!

Item was changed:
  ----- Method: CogARMCompiler>>concretizeSubCqR (in category 'generate machine code - concretize') -----
  concretizeSubCqR
  	"Will get inlined into concretizeAt: switch."
  	"Try whether the quick constant is a small negative number. If it is, optimize."
  	<inline: true>
  	self rotateable8bitImmediate: (operands at: 0)
  		ifTrue: [ :rot :immediate | | reg |
  			reg := self concreteRegister: (operands at: 1).
  			self machineCodeAt: 0 put: (self subs: reg rn: reg imm: immediate ror: rot).
  			^machineCodeSize := 4]
  		ifFalse: [
  			"before building a full load of a big cinstant, see if we can do an add of the constant negated"
  			self rotateable8bitImmediate: (operands at: 0) negated
  				ifTrue: [ :rot :immediate | | reg |
  					reg := self concreteRegister: (operands at: 1).
  					self machineCodeAt: 0 put: (self adds: reg rn: reg imm: immediate ror: rot).
  					^machineCodeSize := 4]
+ 				ifFalse: [^self concretizeDataOperationCwR: 2]].
+ 	^0 "to keep Slang happy"!
- 				ifFalse: [^self concretizeDataOperationCwR: 2]]!

Item was changed:
  ----- Method: CogARMCompiler>>concretizeTstCqR (in category 'generate machine code - concretize') -----
  concretizeTstCqR
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	self rotateable8bitImmediate: (operands at: 0)
  		ifTrue: [ :rot :immediate | | reg |
  			reg := self concreteRegister: (operands at: 1).
  			self machineCodeAt: 0 put: (self tst: reg rn: reg imm: immediate ror: rot).
  			^machineCodeSize := 4]
+ 		ifFalse: [^self concretizeDataOperationCwR: 8].
+ 	^0 "to keep Slang happy"!
- 		ifFalse: [^self concretizeDataOperationCwR: 8]!

Item was removed:
- ----- Method: CogARMCompiler>>cond (in category 'accessing') -----
- cond
- 	^cond!

Item was removed:
- ----- Method: CogARMCompiler>>cond: (in category 'accessing') -----
- cond: condCode
- 	^cond := condCode!

Item was added:
+ ----- Method: CogARMCompiler>>condition (in category 'accessing') -----
+ condition
+ 	^conditionOrNil!

Item was added:
+ ----- Method: CogARMCompiler>>condition: (in category 'accessing') -----
+ condition: condCode
+ 	^conditionOrNil := condCode!

Item was changed:
  ----- Method: CogARMCompiler>>dataOpType:rd:rn:rm:lsr: (in category 'ARM convenience instructions') -----
+ dataOpType: armOpcode rd: destReg rn: srcReg rm: addReg lsr: shft
- dataOpType: opcode rd: destReg rn: srcReg rm: addReg lsr: shft
  "return an {opcode} destReg, srcReg, addReg lsl #shft"
  "important detail - a 0 shft requires setting the shift-type code to 0 to avoid potential instruction confusion"
  	shft = 0
+ 		ifTrue:[^self type: 0 op: armOpcode set: 1 rn: srcReg rd: destReg shifterOperand: addReg]
+ 		ifFalse:[^self type: 0 op: armOpcode set: 1 rn: srcReg rd: destReg shifterOperand: ((shft <<7 bitOr: 32) bitOr:  addReg)]!
- 		ifTrue:[^self type: 0 op: opcode set: 1 rn: srcReg rd: destReg shifterOperand: addReg]
- 		ifFalse:[^self type: 0 op: opcode set: 1 rn: srcReg rd: destReg shifterOperand: ((shft <<7 bitOr: 32) bitOr:  addReg)]!

Item was changed:
  ----- Method: CogARMCompiler>>dispatchConcretize (in category 'generate machine code') -----
  dispatchConcretize
  	"Attempt to generate concrete machine code for the instruction at address.
  	 This is the inner dispatch of concretizeAt: actualAddress which exists only
  	 to get around the branch size limits in the SqueakV3 (blue book derived)
  	 bytecode set."
  	<returnTypeC: #void>
+ 	conditionOrNil ifNotNil:
- 	cond ifNotNil:
  		[self concretizeConditionalInstruction.
  		 ^self].
  		 
  	opcode caseOf: {
  		"Noops & Pseudo Ops"
  		[Label]					-> [^self concretizeLabel].
  		[AlignmentNops]		-> [^self concretizeAlignmentNops].
  		[Fill16]					-> [^self concretizeFill16].
  		[Fill32]					-> [^self concretizeFill32].
  		[FillFromWord]			-> [^self concretizeFillFromWord].
  		[Nop]					-> [^self concretizeNop].
  		"ARM Specific Control/Data Movement" 
  		[LDMFD]				-> [^self concretizeLDMFD].
  		[STMFD]				-> [^self concretizeSTMFD].
  		[SMULL]				-> [^self concretizeSMULL]	.
  		[BICCqR]					-> [^self concretizeDataOperationCqR: BicOpcode].
  		"Control"
  		[Call]						-> [^self concretizeCall]. "call code within code space"
  		[CallFull]					-> [^self concretizeCallFull]. "call code anywhere in address space"
  		[JumpR]						-> [^self concretizeJumpR].
  		[JumpFull]					-> [^self concretizeJumpFull]."jump within address space"
  		[JumpLong]					-> [^self concretizeConditionalJump: AL]."jumps witihn code space"
  		[JumpLongZero]			-> [^self concretizeConditionalJump: EQ].
  		[JumpLongNonZero]		-> [^self concretizeConditionalJump: NE].
  		[Jump]						-> [^self concretizeConditionalJump: AL].
  		[JumpZero]					-> [^self concretizeConditionalJump: EQ].
  		[JumpNonZero]				-> [^self concretizeConditionalJump: NE].
  		[JumpNegative]				-> [^self concretizeConditionalJump: MI].
  		[JumpNonNegative]			-> [^self concretizeConditionalJump: PL].
  		[JumpOverflow]				-> [^self concretizeConditionalJump: VS].
  		[JumpNoOverflow]			-> [^self concretizeConditionalJump: VC].
  		[JumpCarry]				-> [^self concretizeConditionalJump: CS].
  		[JumpNoCarry]				-> [^self concretizeConditionalJump: CC].
  		[JumpLess]					-> [^self concretizeConditionalJump: LT].
  		[JumpGreaterOrEqual]		-> [^self concretizeConditionalJump: GE].
  		[JumpGreater]				-> [^self concretizeConditionalJump: GT].
  		[JumpLessOrEqual]			-> [^self concretizeConditionalJump: LE].
  		[JumpBelow]				-> [^self concretizeConditionalJump: CC]. "unsigned lower"
  		[JumpAboveOrEqual]		-> [^self concretizeConditionalJump: CS]. "unsigned greater or equal"
  		[JumpAbove]				-> [^self concretizeConditionalJump: HI].
  		[JumpBelowOrEqual]		-> [^self concretizeConditionalJump: LS].
  		[JumpFPEqual]				-> [^self concretizeFPConditionalJump: EQ].
  		[JumpFPNotEqual]			-> [^self concretizeFPConditionalJump: NE].
  		[JumpFPLess]				-> [^self concretizeFPConditionalJump: LT].
  		[JumpFPGreaterOrEqual]	-> [^self concretizeFPConditionalJump: GE].
  		[JumpFPGreater]			-> [^self concretizeFPConditionalJump: GT].
  		[JumpFPLessOrEqual]		-> [^self concretizeFPConditionalJump: LE].
  		[JumpFPOrdered]			-> [^self concretizeFPConditionalJump: VC].
  		[JumpFPUnordered]			-> [^self concretizeFPConditionalJump: VS].
  		[RetN]						-> [^self concretizeRetN].
  		[Stop]						-> [^self concretizeStop].
  		"Arithmetic"
  		[AddCqR]					-> [^self concretizeAddCqR].
  		[AddCwR]					-> [^self concretizeDataOperationCwR: AddOpcode].
  		[AddRR]						-> [^self concretizeDataOperationRR: AddOpcode].
  		[AddRdRd]					-> [^self concretizeAddRdRd].
  		[AndCqR]					-> [^self concretizeAndCqR].
  		[AndCqRR]					-> [^self concretizeAndCqRR].
  		[AndCwR]					-> [^self concretizeDataOperationCwR: AndOpcode].
  		[AndRR]						-> [^self concretizeDataOperationRR: AndOpcode].
  		[CmpCqR]					-> [^self concretizeDataOperationCqR: CmpOpcode].
  		[CmpCwR]					-> [^self concretizeDataOperationCwR: CmpOpcode].
  		[CmpRR]					-> [^self concretizeDataOperationRR: CmpOpcode].
  		[CmpRdRd]					-> [^self concretizeCmpRdRd].
  		[DivRdRd]					-> [^self concretizeDivRdRd].
  		[MulRdRd]					-> [^self concretizeMulRdRd].
  		[OrCqR]						-> [^self concretizeDataOperationCqR: OrOpcode].
  		[OrCwR]					-> [^self concretizeDataOperationCwR: OrOpcode].
  		[OrRR]						-> [^self concretizeDataOperationRR: OrOpcode].
  		[SubCqR]					-> [^self concretizeSubCqR].
  		[SubCwR]					-> [^self concretizeDataOperationCwR: SubOpcode].
  		[SubRR]						-> [^self concretizeDataOperationRR: SubOpcode].
  		[SubRdRd]					-> [^self concretizeSubRdRd].
  		[SqrtRd]					-> [^self concretizeSqrtRd].
  		[TstCqR]					-> [^self concretizeTstCqR].
  		[XorCqR]						-> [^self concretizeDataOperationCqR: XorOpcode].
  		[XorCwR]						-> [^self concretizeDataOperationCwR: XorOpcode].
  		[XorRR]							-> [^self concretizeDataOperationRR: XorOpcode].
  		[NegateR]						-> [^self concretizeNegateR].
  		[LoadEffectiveAddressMwrR]	-> [^self concretizeLoadEffectiveAddressMwrR].
  		[ArithmeticShiftRightCqR]		-> [^self concretizeArithmeticShiftRightCqR].
  		[LogicalShiftRightCqR]			-> [^self concretizeLogicalShiftRightCqR].
  		[LogicalShiftLeftCqR]			-> [^self concretizeLogicalShiftLeftCqR].
  		[ArithmeticShiftRightRR]			-> [^self concretizeArithmeticShiftRightRR].
  		[LogicalShiftLeftRR]				-> [^self concretizeLogicalShiftLeftRR].
  		[LogicalShiftRightRR]			-> [^self concretizeLogicalShiftRightRR].
  		"Data Movement"
  		[MoveCqR]			-> [^self concretizeMoveCqR].
  		[MoveCwR]			-> [^self concretizeMoveCwR].
  		[MoveRR]			-> [^self concretizeMoveRR].
  		[MoveAwR]			-> [^self concretizeMoveAwR].
  		[MoveRAw]			-> [^self concretizeMoveRAw].
  		[MoveMbrR]			-> [^self concretizeMoveMbrR].
  		[MoveRMbr]			-> [^self concretizeMoveRMbr].
  		[MoveM16rR]		-> [^self concretizeMoveM16rR].
  		[MoveM64rRd]		-> [^self concretizeMoveM64rRd].
  		[MoveMwrR]		-> [^self concretizeMoveMwrR].
  		[MoveXbrRR]		-> [^self concretizeMoveXbrRR].
  		[MoveRXbrR]		-> [^self concretizeMoveRXbrR].
  		[MoveXwrRR]		-> [^self concretizeMoveXwrRR].
  		[MoveRXwrR]		-> [^self concretizeMoveRXwrR].
  		[MoveRMwr]		-> [^self concretizeMoveRMwr].
  		[MoveRdM64r]		-> [^self concretizeMoveRdM64r].
  		[PopR]				-> [^self concretizePopR].
  		[PushR]				-> [^self concretizePushR].
  		[PushCq]			-> [^self concretizePushCq].
  		[PushCw]			-> [^self concretizePushCw].
  		[PrefetchAw]		-> [^self concretizePrefetchAw].
  		"Conversion"
  		[ConvertRRd]		-> [^self concretizeConvertRRd]}!

Item was changed:
  ----- Method: CogARMCompiler>>genMulR:R: (in category 'abstract instructions') -----
  genMulR: regSource R: regDest
  	"Use SMULL to produce a 64-bit result, implicitly in TempReg,RISCTempReg.
  	 Test the top word for 0 or 1 and set oVerflow if not equal.  Move result in
  	 TempReg into regDest."
- 	<var: #inst type: #AbstractInstruction>
  
  	cogit
  		gen: SMULL operand: regSource operand: regDest; "result in TempReg,RISCTempReg"
  		gen: AddCqR operand: 1 operand: RISCTempReg; "turn -1,0 into 0,1"
  		gen: AddCqR operand: -1 operand: RISCTempReg; "turn 0,1 into not oVerflow"
  		gen: MoveRR operand: TempReg operand: regDest!

Item was changed:
  ----- Method: CogARMCompiler>>is12BitValue:ifTrue:ifFalse: (in category 'testing') -----
  is12BitValue: constant ifTrue: trueAlternativeBlock	ifFalse: falseAlternativeBlock
  	"For LDR and STR, there is an instruction allowing for one instruction encoding if the offset is encodable in signed 12 bit form. pass the trueBlock the value and a 1-bit flag to tell it the sign.
  	The falseBlock can do whatever it needs to, typically building the constant as a full 32bit value and then ld/st with that as a register offset"
+ 	<inline: true>
  	constant abs <= 4095 "(2 raisedTo: 12)-1"
+ 		ifTrue:
+ 			[constant >= 0 
- 		ifTrue: [
- 			constant >= 0 
  				ifTrue: [trueAlternativeBlock value: 1 value: constant]
  				ifFalse: [trueAlternativeBlock value: 0 value: constant abs]]
  		ifFalse: falseAlternativeBlock!

Item was changed:
  ----- Method: CogARMCompiler>>is8BitValue:ifTrue:ifFalse: (in category 'testing') -----
  is8BitValue: constant ifTrue: trueAlternativeBlock	ifFalse: falseAlternativeBlock
  	"For extended LDR and STR for half & double, there is an instruction allowing for one instruction encoding if the offset is encodable in 8 bit."
+ 	<inline: true>
  	constant abs <= 255 "(2 raisedTo: 8)-1"
+ 		ifTrue:
+ 			[constant >= 0 
- 		ifTrue: [
- 			constant >= 0 
  				ifTrue: [trueAlternativeBlock value: 1 value: constant]
  				ifFalse: [trueAlternativeBlock value: 0 value: constant abs]]
  		ifFalse: falseAlternativeBlock!

Item was added:
+ ----- Method: CogARMCompiler>>isPCRelativeValueLoad: (in category 'testing') -----
+ isPCRelativeValueLoad: instr
+ 	<var: 'instr' type: #'unsigned int'>
+ 	"add xx, pc, blah or sub xx, pc, blah"
+ 	^(instr >> 16) = 16rE28F or: [instr >> 16 = 16rE24F]!

Item was added:
+ ----- Method: CogAbstractInstruction class>>ISA (in category 'translation') -----
+ ISA
+ 	"Answer the name of the ISA the receiver's subclass implements."
+ 	^self subclassResponsibility!

Item was added:
+ ----- Method: CogAbstractInstruction class>>identifyingPredefinedMacros (in category 'translation') -----
+ identifyingPredefinedMacros
+ 	"Answer the predefined macros that identify the processors a subclass handles, if any.
+ 	 If the subclass isn't yet ready for production (a work in progress) simply answer nil."
+ 	^nil!

Item was added:
+ ----- Method: CogAbstractInstruction class>>moduleName (in category 'translation') -----
+ moduleName
+ 	"CogAbstractInstruction subclasses collect: [:ea| ea moduleName]"
+ 	^'cogit', self ISA!

Item was added:
+ ----- Method: CogAbstractInstruction class>>translateableSubclasses (in category 'translation') -----
+ translateableSubclasses
+ 	"CogAbstractInstruction translateableSubclasses"
+ 	^self subclasses select: [:compilerClass| compilerClass identifyingPredefinedMacros notNil]!

Item was removed:
- ----- Method: CogAbstractInstruction>>isPCRelativeValueLoad: (in category 'testing') -----
- isPCRelativeValueLoad: instr
- 	<var: 'instr' type: #'unsigned int'>
- 	"add xx, pc, blah or sub xx, pc, blah"
- 	^(instr >> 16) = 16rE28F or: [instr >> 16 = 16rE24F]!

Item was changed:
  ----- Method: CogAbstractInstruction>>outputMachineCodeAt: (in category 'encoding') -----
+ outputMachineCodeAt: targetAddress
- outputMachineCodeAt: address
  	"By default move machine code a byte at a time
  	  Subclasses with coarser granularity can override as desired."
  	<inline: true>
  	0 to: machineCodeSize - 1 do:
  		[:j|
+ 		objectMemory byteAt: targetAddress + j put: (machineCode at: j)]!
- 		objectMemory byteAt: address + j put: (machineCode at: j)]!

Item was added:
+ ----- Method: CogIA32Compiler class>>ISA (in category 'translation') -----
+ ISA
+ 	"Answer the name of the ISA the receiver implements."
+ 	^#IA32!

Item was added:
+ ----- Method: CogIA32Compiler class>>identifyingPredefinedMacros (in category 'translation') -----
+ identifyingPredefinedMacros
+ 	^#('_M_I386' '_X86_' 'i386' 'i486' 'i586' 'i686' '__i386__' '__386__' 'X86' 'I386')!

Item was added:
+ ----- Method: CogMethodZone>>initialize (in category 'initialization') -----
+ initialize
+ 	"Make youngReferrers arithmetic for addressIsInCodeZone:"
+ 	youngReferrers := 0!

Item was changed:
  ----- Method: CogObjectRepresentationFor32BitSpur>>genGetActiveContextLarge:inBlock: (in category 'initialization') -----
  genGetActiveContextLarge: isLarge inBlock: isInBlock
  	"Create a trampoline to answer the active context that will
  	 answer it if a frame is already married, and create it otherwise.
  	 Assume numArgs is in SendNumArgsReg and ClassReg is free."
  	| header slotSize jumpSingle loopHead jumpNeedScavenge continuation exit |
  	<var: #jumpNeedScavenge type: #'AbstractInstruction *'>
  	<var: #continuation type: #'AbstractInstruction *'>
  	<var: #jumpSingle type: #'AbstractInstruction *'>
  	<var: #loopHead type: #'AbstractInstruction *'>
  	<var: #exit type: #'AbstractInstruction *'>
  	cogit "load the flag; stash it in both TempReg & ClassReg; do the compare (a prime candidated for use of AndCq:R:R:)"
  		MoveMw: FoxMethod r: FPReg R: ClassReg;
  		AndCq: MFMethodFlagHasContextFlag R: ClassReg R: TempReg.
  	jumpSingle := cogit JumpZero: 0. "jump if flag bit not set"
  	cogit "since the flag bit was set, get the context in the receiver reg and return"
  		MoveMw: FoxThisContext r: FPReg R: ReceiverResultReg;
  		RetN: 0.
  	jumpSingle jmpTarget: cogit Label.
  
  	"OK, it doesn't exist; instantiate and initialize it"
  	"set the hasContext flag; See CoInterpreter class>>initializeFrameIndices"
  	cogit
  		OrCq: MFMethodFlagHasContextFlag R: ClassReg;
  		MoveR: ClassReg Mw: FoxMethod r: FPReg.
  	"now get the home CogMethod into ClassReg and save for post-instantiation."
  	isInBlock
  		ifTrue:
  			[cogit
  				SubCq: 3 R: ClassReg; "-3 is -(hasContext+isBlock) flags"
  				MoveM16: 0 r: ClassReg R: TempReg;
  				SubR: TempReg R: ClassReg]
  		ifFalse:
  			[cogit SubCq: 1 R: ClassReg]. "-1 is hasContext flag"
  
  	"instantiate the context..."
  	slotSize := isLarge ifTrue: [LargeContextSlots] ifFalse: [SmallContextSlots].
  	header := objectMemory
  					headerForSlots: slotSize
  					format: objectMemory indexablePointersFormat
  					classIndex: ClassMethodContextCompactIndex.
  	self flag: #endianness.
  	cogit
  		MoveAw: objectMemory freeStartAddress R: ReceiverResultReg;
  		MoveCq: (self low32BitsOf: header) R: TempReg;
  		MoveR: TempReg Mw: 0 r: ReceiverResultReg;
  		MoveCq: header >> 32 R: TempReg;
  		MoveR: TempReg Mw: 4 r: ReceiverResultReg;
  		MoveR: ReceiverResultReg R: TempReg;
  		AddCq: (objectMemory smallObjectBytesForSlots: slotSize) R: TempReg;
  		MoveR: TempReg Aw: objectMemory freeStartAddress;
  		CmpCq: objectMemory getScavengeThreshold R: TempReg.
  	jumpNeedScavenge := cogit JumpAboveOrEqual: 0.
  
  	"Now initialize the fields of the context.  See CoInterpreter>>marryFrame:SP:copyTemps:"
  	"sender gets frame pointer as a SmallInteger"
  	continuation :=
  	cogit MoveR: FPReg R: TempReg.
  	self genSetSmallIntegerTagsIn: TempReg.
  	cogit MoveR: TempReg Mw: objectMemory baseHeaderSize + (SenderIndex * objectMemory bytesPerOop) r: ReceiverResultReg.
  
  	"pc gets frame caller as a SmallInteger"
  	cogit MoveMw: FoxSavedFP r: FPReg R: TempReg.
  	self genSetSmallIntegerTagsIn: TempReg.
  	cogit MoveR: TempReg Mw: objectMemory baseHeaderSize + (InstructionPointerIndex * objectMemory bytesPerOop) r: ReceiverResultReg.
  
  	"Set the method field, freeing up ClassReg again, and frame's context field,"
  	cogit
  		MoveMw: (cogit offset: CogMethod of: #methodObject) r: ClassReg R: TempReg;
  		MoveR: TempReg Mw: objectMemory baseHeaderSize + (MethodIndex * objectMemory wordSize) r: ReceiverResultReg;
  		MoveR: ReceiverResultReg Mw: FoxThisContext r: FPReg.
  
  	"Now compute stack pointer; this is stackPointer (- 1 for return pc if a CISC) - framePointer - 4 (1 each for saved pc, method, context, receiver) + 1 (1-relative) + numArgs"
  	"TPR note - the code here is actually doing
  	context stackPointer := ((((fp - sp) / 4) - [3|4]) + num args) asSmallInteger"
  	cogit
  		MoveR: FPReg R: TempReg;
  		SubR: SPReg R: TempReg;
  		LogicalShiftRightCq: self log2BytesPerWord R: TempReg;
  		SubCq: (cogit backEnd hasLinkRegister ifTrue: [3] ifFalse: [4]) R: TempReg;
  		AddR: SendNumArgsReg R: TempReg.
  	self genConvertIntegerToSmallIntegerInReg: TempReg.
  	cogit MoveR: TempReg Mw: objectMemory baseHeaderSize + (StackPointerIndex * objectMemory bytesPerOop) r: ReceiverResultReg.
  
  	"Set closureOrNil to either the stacked receiver or nil"
  	isInBlock
  		ifTrue:
  			[cogit
  				MoveR: SendNumArgsReg R: TempReg;
  				AddCq: 2 R: TempReg; "+2 for saved fp and saved pc"
  				MoveXwr: TempReg R: FPReg R: TempReg]
  		ifFalse:
  			[cogit MoveCw: objectMemory nilObject R: TempReg].
  	cogit MoveR: TempReg Mw: objectMemory baseHeaderSize + (ClosureIndex * objectMemory bytesPerOop) r: ReceiverResultReg.
  
  	"Set the receiver"
  	cogit
  		MoveMw: FoxMFReceiver r: FPReg R: TempReg;
  		MoveR: TempReg Mw: objectMemory baseHeaderSize + (ReceiverIndex * objectMemory bytesPerOop) r: ReceiverResultReg.
  
  	"Now copy the arguments.  This is tricky because of the shortage of registers,.  ClassReg ranges
  	 from 1 to numArgs (SendNumArgsReg), and from ReceiverIndex + 1 to ReceiverIndex + numArgs.
  	 1 to: numArgs do:
  		[:i|
  		temp := longAt(FPReg + ((SendNumArgs - i + 2) * BytesPerWord)). +2 for saved pc and savedfp
  		longAtput(FPReg + FoxMFReceiver + (i * BytesPerWord), temp)]"
  	"TPR note: this is a prime candidate for passing off to the backend to do at least faintly optimal code"
  	cogit MoveCq: 1 R: ClassReg.
  	loopHead := cogit CmpR: SendNumArgsReg R: ClassReg.
  	exit := cogit JumpGreater: 0.
  	cogit
  		MoveR: SendNumArgsReg R: TempReg;
  		SubR: ClassReg R: TempReg;
  		AddCq: 2 R: TempReg; "+2 for saved fp and saved pc"
  		MoveXwr: TempReg R: FPReg R: TempReg;
  		AddCq: ReceiverIndex + (objectMemory baseHeaderSize / objectMemory wordSize) R: ClassReg; "Now convert ClassReg from frame index to context index"
  		MoveR: TempReg Xwr: ClassReg R: ReceiverResultReg;
  		SubCq: ReceiverIndex + (objectMemory baseHeaderSize / objectMemory wordSize) - 1 R: ClassReg; "convert back adding 1 ;-)"
  		Jump: loopHead.
  	exit jmpTarget: cogit Label.
  
  	"Finally nil or copy the non-argument temps.
  	 ClassReg := FPReg + FoxMFReceiver.
  	 SendNumArgsReg := SendNumArgsReg+ReceiverIndex.
  	 [ClassReg := ClassReg - 4.
  	  backEnd hasLinkRegister
  			ifTrue: [ClassReg > SPReg]
  			ifFalse: [ClassReg >= SPReg]] whileTrue:
  		[receiver[SendNumArgsReg] := *ClassReg.
  		 SendNumArgsReg := SendNumArgsReg + 1]]"
  	coInterpreter marryFrameCopiesTemps ifFalse:
  		[cogit MoveCq: objectMemory nilObject R: TempReg].
  	cogit
  		MoveR: FPReg R: ClassReg;
  		AddCq: FoxMFReceiver R: ClassReg;
  		AddCq: ReceiverIndex + 1 + (objectMemory baseHeaderSize / objectMemory wordSize) R: SendNumArgsReg.
  	loopHead :=
  	cogit SubCq: objectMemory wordSize R: ClassReg.
  	cogit CmpR: SPReg R: ClassReg.
  	"If on a CISC there's a retpc for the trampoline call on top of stack; if on a RISC there isn't."
  	exit := cogit backEnd hasLinkRegister
  				ifTrue: [cogit JumpBelow: 0]
  				ifFalse: [cogit JumpBelowOrEqual: 0].
  	coInterpreter marryFrameCopiesTemps ifTrue:
  		[cogit MoveMw: 0 r: ClassReg R: TempReg].
  	cogit
  		MoveR: TempReg Xwr: SendNumArgsReg R: ReceiverResultReg;
  		AddCq: 1 R: SendNumArgsReg;
  		Jump: loopHead.
  	exit jmpTarget: cogit Label.
  
  	cogit RetN: 0.
  	
+ 	jumpNeedScavenge jmpTarget: cogit Label.
+ 	cogit backEnd saveAndRestoreLinkRegAround:
+ 		[cogit CallRT: ceScheduleScavengeTrampoline].
- 	jumpNeedScavenge jmpTarget:
- 		(cogit backEnd saveAndRestoreLinkRegAround: [cogit CallRT: ceScheduleScavengeTrampoline]). "We need to push the LR here for ARM, and pop it back after the callRT:"
  	cogit Jump: continuation.
  	^0!

Item was added:
+ ----- Method: Cogit class>>activeCompilerClass (in category 'translation') -----
+ activeCompilerClass
+ 	^CogAbstractInstruction subclasses detect: [:compilerClass| compilerClass ISA == (initializationOptions at: #ISA)]!

Item was changed:
  ----- Method: Cogit class>>ancilliaryClasses: (in category 'translation') -----
  ancilliaryClasses: options
  	ProcessorClass ifNil:
  		[Cogit initializeMiscConstants].
  	^{	CogMethodZone.
  		CogAbstractInstruction.
+ 		self activeCompilerClass.
- 		ProcessorClass basicNew abstractInstructionCompilerClass.
  		CogBlockStart.
  		CogBytecodeDescriptor.
  		CogBytecodeFixup.
  		CogInstructionAnnotation.
  		CogPrimitiveDescriptor.
  		CogBlockMethod.
  		CogMethod },
  	((options at: #NewspeakVM ifAbsent: [false])
  		ifTrue: [{NewspeakCogMethod. NSSendCache}]
  		ifFalse: [#()])!

Item was added:
+ ----- Method: Cogit class>>generateCodeStringForCogitDotC (in category 'translation') -----
+ generateCodeStringForCogitDotC
+ 	"Generate a skeletal cogit.c that includes the relevant
+ 	 cogitFOO.c for each subclass of CogAbstractInstruction."
+ 	 
+ 	^String streamContents:
+ 		[:s|
+ 		 s nextPutAll: '/* Automatically generated by\	' withCRs.
+ 		 s nextPutAll: (CCodeGenerator monticelloDescriptionFor: self).
+ 		 s cr; nextPutAll: ' */'.
+ 		 s cr; cr; nextPut: $#.
+ 		 (CogAbstractInstruction subclasses sort: [:a :b| a name < b name]) do:
+ 			[:class |
+ 			class identifyingPredefinedMacros ifNotNil:
+ 				[:predefinedMacros|
+ 				 s nextPutAll: 'if '.
+ 				 predefinedMacros
+ 					do: [:predefinedMacro| s nextPutAll: 'defined('; nextPutAll: predefinedMacro; nextPut: $)]
+ 					separatedBy: [s nextPutAll: ' || '].
+ 				 s cr; cr; nextPutAll: '#	include "'; nextPutAll: class moduleName; nextPutAll: '.c"'.
+ 				 s cr; cr; nextPutAll: '#el']].
+ 		 s nextPutAll: 'se'.
+ 		 #(	'As yet no Cogit implementation appears to exist for your platform.'
+ 			'Consider implementing it, starting by adding a subclass of CogAbstractInstruction.') do:
+ 			[:msg| s cr; nextPutAll: '#	error '; nextPutAll: msg].
+ 		 s cr; nextPutAll: '#endif'; cr]!

Item was changed:
  ----- Method: Cogit class>>initializeMiscConstants (in category 'class initialization') -----
  initializeMiscConstants
  	super initializeMiscConstants.
  	Debug := initializationOptions at: #Debug ifAbsent: [false].
  	(initializationOptions includesKey: #EagerInstructionDecoration)
  		ifTrue:
  			[EagerInstructionDecoration := initializationOptions at: #EagerInstructionDecoration]
  		ifFalse:
  			[EagerInstructionDecoration isNil ifTrue:
  				[EagerInstructionDecoration := false]]. "speeds up single stepping but could lose fidelity"
  
+ 	ProcessorClass := (initializationOptions at: #ISA ifAbsentPut: [#IA32]) caseOf: {
- 	ProcessorClass := (initializationOptions at: #ISA ifAbsent: [#IA32]) caseOf: {
  							[#IA32] 	->	[BochsIA32Alien].
  							[#ARMv5]	->	[GdbARMAlien]. }.
  
  	"Our criterion for which methods to JIT is literal count.  The default value is 60 literals or less."
  	MaxLiteralCountForCompile := initializationOptions at: #MaxLiteralCountForCompile ifAbsent: [60].
  	"we special-case 0, 1 & 2 argument sends, N is numArgs >= 3"
  	NumSendTrampolines := 4.
  	"Currently not even the ceImplicitReceiverTrampoline contains object references."
  	NumObjRefsInRuntime := 0.
  
  	NSCSelectorIndex := (NSSendCache instVarNames indexOf: #selector) - 1.
  	NSCNumArgsIndex := (NSSendCache instVarNames indexOf: #numArgs) - 1.
  	NSCClassTagIndex := (NSSendCache instVarNames indexOf: #classTag) - 1.
  	NSCEnclosingObjectIndex := (NSSendCache instVarNames indexOf: #enclosingObject) - 1.
  	NSCTargetIndex := (NSSendCache instVarNames indexOf: #target) - 1.
  	NumOopsPerNSC := NSSendCache instVarNames size.
  
  	"Max size to alloca when compiling.
  	 Mac OS X 10.6.8 segfaults approaching 8Mb.
  	 Linux 2.6.9 segfaults above 11Mb.
  	 WIndows XP segfaults approaching 2Mb."
  	MaxStackAllocSize := 1024 * 1024 * 3 / 2 !

Item was added:
+ ----- Method: Cogit class>>processorSpecificSourceFileName (in category 'translation') -----
+ processorSpecificSourceFileName
+ 	^self activeCompilerClass moduleName, '.c'!

Item was changed:
  ----- Method: Cogit>>addressIsInCodeZone: (in category 'testing') -----
  addressIsInCodeZone: address
  	"N.B. We /don't/ write this as address between: codeBase and: methodZone limitZony in case we're
  	 testing an address in a method whose code has yet to be allocated and is hence >= methodZone limitZony"
  	^address asUnsignedInteger >= codeBase
+ 	  and: [address < methodZone youngReferrers]!
- 	  and: [address < (methodZone youngReferrers ifNil: [0])]!

Item was changed:
  ----- Method: VMMaker class>>generateEitherSqueakCogVM (in category 'configurations') -----
  generateEitherSqueakCogVM
  	| coInterpreterClass |
  	coInterpreterClass := self chooseCoInterpreterClassIfAbsent: [^self].
  	^self generateSqueakCogVMWithInterpreterClass: coInterpreterClass
+ 		  options: ((coInterpreterClass includesBehavior: CoInterpreterMT)
- 		  options: #( ISA IA32),
- 					((coInterpreterClass includesBehavior: CoInterpreterMT)
  						ifTrue: [#(COGMTVM true)]
  						ifFalse: [#()])!

Item was changed:
  ----- Method: VMMaker class>>generateNewspeakSpurCogVM (in category 'configurations') -----
  generateNewspeakSpurCogVM
  	"No primitives since we can use those for the Cog Newspeak VM"
  	^VMMaker
  		generate: CoInterpreter
  		and: StackToRegisterMappingCogit
  		with: #(	ObjectMemory Spur32BitCoMemoryManager
  				MULTIPLEBYTECODESETS true
+ 				NewspeakVM true)
- 				NewspeakVM true
- 				ISA IA32)
  		to: (FileDirectory default pathFromURI: self sourceTree, '/nsspursrc')
  		platformDir: (FileDirectory default pathFromURI: self sourceTree, '/platforms')
  		including:#(	AsynchFilePlugin BMPReadWriterPlugin BalloonEnginePlugin BitBltSimulation
  					DeflatePlugin DSAPlugin DropPlugin FileCopyPlugin FilePlugin FloatArrayPlugin FloatMathPlugin
  					ImmX11Plugin JPEGReadWriter2Plugin JPEGReaderPlugin LargeIntegersPlugin
  					Matrix2x3Plugin MiscPrimitivePlugin NewsqueakIA32ABIPlugin RePlugin
  					SecurityPlugin SocketPlugin SoundPlugin SqueakSSLPlugin SurfacePlugin
  					UUIDPlugin UnixOSProcessPlugin UnixAioPlugin
  					VMProfileLinuxSupportPlugin VMProfileMacSupportPlugin Win32OSProcessPlugin)
  !

Item was changed:
  ----- Method: VMMaker class>>generateSqueakSpurCogSistaVM (in category 'configurations') -----
  generateSqueakSpurCogSistaVM
  	"No primitives since we can use those for the Cog VM"
  	^VMMaker
  		generate: CoInterpreter
  		and: SistaStackToRegisterMappingCogit
  		with: #(	SistaVM true
  				ObjectMemory Spur32BitCoMemoryManager
  				MULTIPLEBYTECODESETS true
- 				ISA IA32
  				bytecodeTableInitializer initializeBytecodeTableForSqueakV3PlusClosuresSistaV1Hybrid)
  		to: (FileDirectory default pathFromURI: self sourceTree, '/spursistasrc')
  		platformDir: (FileDirectory default pathFromURI: self sourceTree, '/platforms')
  		including:#()!

Item was changed:
  ----- Method: VMMaker class>>generateSqueakSpurCogVM (in category 'configurations') -----
  generateSqueakSpurCogVM
  	"No primitives since we can use those for the Cog VM"
  	^VMMaker
  		generate: CoInterpreter
  		and: StackToRegisterMappingCogit
+ 		with: #(ObjectMemory Spur32BitCoMemoryManager)
- 		with: #(	ObjectMemory Spur32BitCoMemoryManager
- 				ISA IA32)
  		to: (FileDirectory default pathFromURI: self sourceTree, '/spursrc')
  		platformDir: (FileDirectory default pathFromURI: self sourceTree, '/platforms')
  		including:#()!

Item was added:
+ ----- Method: VMMaker class>>oldFileNamed: (in category 'utilities') -----
+ oldFileNamed: aFilename
+ 	"Always output files in unix lf format.
+ 		A single format is friendlier to e.g. external version control systems.
+ 		The Microsoft and old MacOS classic C compilers all accept lf format files."
+ 
+ 	^(MultiByteFileStream oldFileNamed: aFilename)
+ 		lineEndConvention: #lf;
+ 		yourself!

Item was removed:
- ----- Method: VMMaker>>generateCogitFile (in category 'generate sources') -----
- generateCogitFile
- 	"Translate the Smalltalk description of the virtual machine into C.  If 'self doInlining' is true, small method bodies are inlined to reduce procedure call overhead.  On the PPC, this results in a factor of three speedup with only 30% increase in code size.  Subclasses can use specialised versions of CCodeGenerator and interpreterClass."
- 
- 	| cg cogitClass |
- 	(cogitClass := self interpreterClass cogitClass) ifNil: [^nil].
- 	cg := [self buildCodeGeneratorForCogit]
- 			on: Notification
- 			do: [:ex|
- 				ex tag == #getVMMaker
- 					ifTrue: [ex resume: self]
- 					ifFalse: [(ex respondsTo: #rearmHandlerDuring:)
- 								ifTrue: [ex rearmHandlerDuring: [ex pass]]
- 								ifFalse: [ex pass]]].
- 	self needsToRegenerateCogitFile ifFalse: [^nil].
- 
- 	cg inferTypesForImplicitlyTypedVariablesAndMethods.
- 
- 	cg vmClass preGenerationHook: cg.
- 	cg storeCodeOnFile: (self sourceFilePathFor: cogitClass sourceFileName) doInlining: cogitClass doInlining.
- 	cg vmClass additionalHeadersDo:
- 		[:headerName :headerContents| | filePath |
- 		 filePath := self coreVMDirectory fullNameFor: headerName.
- 		 (cg needToGenerateHeader: headerName file: filePath contents: headerContents) ifTrue:
- 			 [cg storeHeaderOnFile: filePath contents: headerContents]].
- 	cogitClass apiExportHeaderName ifNotNil:
- 		[cg storeAPIExportHeader: cogitClass apiExportHeaderName
- 			OnFile: (self sourceFilePathFor: cogitClass apiExportHeaderName)]!

Item was added:
+ ----- Method: VMMaker>>generateCogitFileFor: (in category 'generate sources') -----
+ generateCogitFileFor: cogitClass
+ 	"Translate the Smalltalk description of the virtual machine into C.  If 'self doInlining' is true, small method bodies are inlined to reduce procedure call overhead.  On the PPC, this results in a factor of three speedup with only 30% increase in code size.  Subclasses can use specialised versions of CCodeGenerator and interpreterClass."
+ 
+ 	| cg |
+ 	cg := [self buildCodeGeneratorForCogit]
+ 			on: Notification
+ 			do: [:ex|
+ 				ex tag == #getVMMaker
+ 					ifTrue: [ex resume: self]
+ 					ifFalse: [(ex respondsTo: #rearmHandlerDuring:)
+ 								ifTrue: [ex rearmHandlerDuring: [ex pass]]
+ 								ifFalse: [ex pass]]].
+ 	self needsToRegenerateCogitFile ifFalse: [^nil].
+ 
+ 	cg inferTypesForImplicitlyTypedVariablesAndMethods.
+ 
+ 	cg vmClass preGenerationHook: cg.
+ 	cg storeCodeOnFile: (self sourceFilePathFor: cogitClass processorSpecificSourceFileName) doInlining: cogitClass doInlining.
+ 	^cg!

Item was added:
+ ----- Method: VMMaker>>generateCogitFiles (in category 'generate sources') -----
+ generateCogitFiles
+ 	"Translate the Smalltalk description of the virtual machine into C.  If 'self doInlining' is true, small method bodies are inlined to reduce procedure call overhead.  On the PPC, this results in a factor of three speedup with only 30% increase in code size.  Subclasses can use specialised versions of CCodeGenerator and interpreterClass."
+ 
+ 	| cogitClass cg |
+ 	(cogitClass := self interpreterClass cogitClass) ifNil: [^nil].
+ 	self generateCogitIncludeFileFor: cogitClass.
+ 	CogAbstractInstruction translateableSubclasses do:
+ 		[:compilerClass|
+ 		optionsDictionary at: #ISA put: compilerClass ISA.
+ 		cg := self generateCogitFileFor: cogitClass].
+ 	cg vmClass additionalHeadersDo:
+ 		[:headerName :headerContents| | filePath |
+ 		 filePath := self coreVMDirectory fullNameFor: headerName.
+ 		 (cg needToGenerateHeader: headerName file: filePath contents: headerContents) ifTrue:
+ 			 [cg storeHeaderOnFile: filePath contents: headerContents]].
+ 	cogitClass apiExportHeaderName ifNotNil:
+ 		[cg storeAPIExportHeader: cogitClass apiExportHeaderName
+ 			OnFile: (self sourceFilePathFor: cogitClass apiExportHeaderName)]!

Item was added:
+ ----- Method: VMMaker>>generateCogitIncludeFileFor: (in category 'generate sources') -----
+ generateCogitIncludeFileFor: cogitClass
+ 	"Generate the skeletal cogit.c that includes the processor-specific cogit files."
+ 
+ 	| code fileName file |
+ 	code := Cogit generateCodeStringForCogitDotC.
+ 	fileName := self coreVMDirectory fullNameFor: cogitClass sourceFileName.
+ 	((self coreVMDirectory fileExists: cogitClass sourceFileName)
+ 	and: [(self class oldFileNamed: fileName) contents = code]) ifFalse:
+ 		[file := self class forceNewFileNamed: fileName.
+ 		 [file nextPutAll: code] ensure:
+ 			[file close]]!

Item was changed:
  ----- Method: VMMaker>>generateMainVM (in category 'generate sources') -----
  generateMainVM
  	"Generate the interp (and optionally the cogit), internal plugins and exports.
  	 N.B. generateInterpreterFile *must* preceed generateCogitFile so that
  	 the objectMemory and interpreter classes are initialized before the Cogit
  	 code is generated."
  
  	self generateInterpreterFile;
+ 		generateCogitFiles;
- 		generateCogitFile;
  		processFilesForCoreVM;
  		generateInternalPlugins;
  		generateExportsFile!

Item was changed:
  ----- Method: VMMaker>>needsToRegenerateCogitFile (in category 'generate sources') -----
  needsToRegenerateCogitFile
  	"Check the timestamp for the relevant classes and then the timestamp for the main source file (e.g. interp.c)
  	 file if it already exists. Answer if the file needs regenerating."
  
  	| cogitClass cogitClasses tStamp |
  	cogitClasses := (cogitClass := self interpreterClass cogitClass) withAllSuperclasses copyUpThrough: Cogit.
  	cogitClasses addAllLast: (cogitClass ancilliaryClasses: self options).
  	tStamp := cogitClasses inject: 0 into: [:tS :cl| tS max: cl timeStamp].
  
  	"don't translate if the file is newer than my timeStamp"
+ 	(self coreVMDirectory entryAt: cogitClass processorSpecificSourceFileName ifAbsent: [nil]) ifNotNil:
- 	(self coreVMDirectory entryAt: cogitClass sourceFileName ifAbsent: [nil]) ifNotNil:
  		[:fstat|
  		tStamp < fstat modificationTime ifTrue:
+ 			[^self confirm: ('The ', self configurationNameIfAny, cogitClass printString,
+ 							', ', cogitClass activeCompilerClass, '\classes have not been modified since the ',
+ 							cogitClass processorSpecificSourceFileName,
+ 							' source file\was last generated.  Do you still want to regenerate it?') withCRs]].
+ 	^true!
- 			[^self confirm: 'The ', self configurationNameIfAny, cogitClass printString, ' classes have not been modified since\ the source file was last generated.\Do you still want to regenerate it?' withCRs]].
- 	^true
- !



More information about the Vm-dev mailing list