[Vm-dev] VM Maker: VMMaker-oscog-EstebanLorenzano.302.mcz

commits at source.squeak.org commits at source.squeak.org
Wed Jul 10 12:40:50 UTC 2013


Esteban Lorenzano uploaded a new version of VMMaker to project VM Maker:
http://source.squeak.org/VMMaker/VMMaker-oscog-EstebanLorenzano.302.mcz

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

Name: VMMaker-oscog-EstebanLorenzano.302
Author: EstebanLorenzano
Time: 10 July 2013, 2:35:56.127 pm
UUID: 99d6632c-06ac-4f19-b842-b6807ad969e9
Ancestors: VMMaker-oscog-GuillermoPolito.243, VMMaker.oscog-tpr.301

- merged with Eliot's

=============== Diff against VMMaker-oscog-GuillermoPolito.243 ===============

Item was changed:
  ----- Method: BitBltSimulation class>>declareCVarsIn: (in category 'translation') -----
  declareCVarsIn: aCCodeGenerator
+ 
+ 	"add option of  fast path BitBLT code header"
+ 	aCCodeGenerator
+ 		addHeaderFile:'#ifdef ENABLE_FAST_BLT
+ #include "BitBltDispatch.h"
+ #else
+ // to handle the unavoidable decl in the spec of copyBitsFallback();
+ #define operation_t void
+ #endif'.
+ 		
  	aCCodeGenerator var: 'opTable'
  		declareC: 'void *opTable[' , OpTableSize printString , ']'.
  	aCCodeGenerator var: 'maskTable'
  		declareC:'int maskTable[33] = {
  0, 1, 3, 0, 15, 31, 0, 0, 255, 0, 0, 0, 0, 0, 0, 0, 65535,
  0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, -1
  }'.
  	aCCodeGenerator var: 'ditherMatrix4x4'
  		declareC:'const int ditherMatrix4x4[16] = {
  0,	8,	2,	10,
  12,	4,	14,	6,
  3,	11,	1,	9,
  15,	7,	13,	5
  }'.
  	aCCodeGenerator var: 'ditherThresholds16'
  		declareC:'const int ditherThresholds16[8] = { 0, 2, 4, 6, 8, 12, 14, 16 }'.
  	aCCodeGenerator var: 'ditherValues16'
  		declareC:'const int ditherValues16[32] = {
  0, 0, 1, 2, 3, 4, 5, 6, 7, 8, 9, 10, 11, 12, 13, 14,
  15, 16, 17, 18, 19, 20, 21, 22, 23, 24, 25, 26, 27, 28, 29, 30
  }'.
  
  	aCCodeGenerator var: 'warpBitShiftTable'
  		declareC:'int warpBitShiftTable[32]'.
  
  	aCCodeGenerator var:'cmShiftTable' 
  		type:'int *'.
  	aCCodeGenerator var:'cmMaskTable' 
  		type:'unsigned int *'.
  	aCCodeGenerator var:'cmLookupTable' 
  		type:'unsigned int *'.
  
  	aCCodeGenerator var: 'dither8Lookup'
  		declareC:' unsigned char dither8Lookup[4096]'.
  
  	aCCodeGenerator var:'ungammaLookupTable' 
  		type: 'unsigned char *'.
  	aCCodeGenerator var:'gammaLookupTable' 
  		type: 'unsigned char *'.
  
  	aCCodeGenerator var: 'querySurfaceFn' type: 'void *'.
  	aCCodeGenerator var: 'lockSurfaceFn' type: 'void *'.
  	aCCodeGenerator var: 'unlockSurfaceFn' type: 'void *'!

Item was changed:
  ----- Method: BitBltSimulation>>copyBits (in category 'setup') -----
  copyBits
  	"This function is exported for the Balloon engine"
  	<export: true>
  	<inline: false>
  	self clipRange.
  	(bbW <= 0 or: [bbH <= 0]) ifTrue:
  		["zero width or height; noop"
  		affectedL := affectedR := affectedT := affectedB := 0.
  		^ nil].
  	"Lock the surfaces"
  	self lockSurfaces ifFalse:[^interpreterProxy primitiveFail].
+ 
+ 	self
+ 		cppIf: #'ENABLE_FAST_BLT'
+ 		ifTrue:["you really, really mustn't call this unless you have the rest of the code to link to"
+ 			self copyBitsFastPathSpecialised]
+ 		ifFalse:[self copyBitsLockedAndClipped].
+ 
- 	self copyBitsLockedAndClipped.
  	self unlockSurfaces.!

Item was added:
+ ----- Method: BitBltSimulation>>copyBits:Fallback: (in category 'setup') -----
+ copyBits: op Fallback: flags
+ 	"Recover from the fast path specialised code saying Help-I-cant-cope"
+ 	|done |
+ 	<static: false>
+ 	<returnTypeC: 'void'>
+ 	<inline: false>
+ 	<var: #op type: 'operation_t *'>
+ 	<var: #flags type:'unsigned int'>
+ 	self cppIf: #'ENABLE_FAST_BLT'
+ 		ifTrue:[
+ 			"recover values from the operation struct used by the fast ARM code"
+ 			self cCode:'
+ 	combinationRule = op->combinationRule;
+ 	noSource = op->noSource;
+ 	sourceBits = (sqInt) op->src.bits;
+ 	sourcePitch = op->src.pitch;
+ 	sourceDepth = op->src.depth;
+ 	sourceMSB = op->src.msb;
+ 	sx = op->src.x;
+ 	sy = op->src.y;
+ 	destBits = (sqInt) op->dest.bits;
+ 	destPitch = op->dest.pitch;
+ 	destDepth = op->dest.depth;
+ 	destMSB = op->dest.msb;
+ 	dx = op->dest.x;
+ 	dy = op->dest.y;
+ 	bbW = op->width;
+ 	bbH = op->height;
+ 	cmFlags = op->cmFlags;
+ 	cmShiftTable = (void *) op->cmShiftTable;
+ 	cmMaskTable = (void *) op->cmMaskTable;
+ 	cmMask = op->cmMask;
+ 	cmLookupTable = (void *) op->cmLookupTable;
+ 	noHalftone = op->noHalftone;
+ 	halftoneHeight = op->halftoneHeight;
+ 	halftoneBase = (sqInt) op->halftoneBase;
+ 	if (combinationRule == 30 || combinationRule == 31) {
+ 		sourceAlpha = op->opt.sourceAlpha;
+ 	}
+ 	if (combinationRule == 41) {
+ 		componentAlphaModeColor = op->opt.componentAlpha.componentAlphaModeColor;
+ 		componentAlphaModeAlpha = op->opt.componentAlpha.componentAlphaModeAlpha;
+ 		gammaLookupTable = (void *) op->opt.componentAlpha.gammaLookupTable;
+ 		ungammaLookupTable = (void *) op->opt.componentAlpha.ungammaLookupTable;
+ 	}'.
+ 	
+ 				destPPW := 32 / destDepth.
+ 				cmBitsPerColor := 0.
+ 				cmMask = 16r1FF ifTrue: [cmBitsPerColor := 3].
+ 				cmMask = 16rFFF ifTrue: [cmBitsPerColor := 4].
+ 				cmMask = 16r3FFF ifTrue: [cmBitsPerColor := 5].
+ 	
+ 				"Try a shortcut for stuff that should be run as quickly as possible"
+ 				done := self tryCopyingBitsQuickly.
+ 				done ifTrue:[^nil].
+ 
+ 				bitCount := 0.
+ 				"Choose and perform the actual copy loop."
+ 				self performCopyLoop]
+ 
+ 	
+ 
+ 
+ !

Item was added:
+ ----- Method: BitBltSimulation>>copyBitsFastPathSpecialised (in category 'setup') -----
+ copyBitsFastPathSpecialised
+ 	"Perform the actual copyBits operation using the fast path specialised code; fail some cases by falling back to normal code.
+ 	Assume: Surfaces have been locked and clipping was performed."
+ 	<inline: false>
+ 
+ 	self
+ 		cppIf: #'ENABLE_FAST_BLT'
+ 		ifTrue:[
+ 	"set the affected area to 0 first"
+ 	affectedL := affectedR := affectedT := affectedB := 0.
+ 	
+ 	self copyBitsRule41Test.	
+ 	(interpreterProxy failed not)
+ 		ifFalse: [^ interpreterProxy primitiveFail].
+ 
+  	"we skip the tryCopyingBitsQuickly and leave that to falback code"
+ 	 
+ 	(combinationRule = 30) | (combinationRule = 31) ifTrue:
+ 		["Check and fetch source alpha parameter for alpha blend"
+ 		interpreterProxy methodArgumentCount = 1
+ 			ifTrue: [sourceAlpha := interpreterProxy stackIntegerValue: 0.
+ 					(interpreterProxy failed not and: [(sourceAlpha >= 0) & (sourceAlpha <= 255)])
+ 						ifFalse: [^ interpreterProxy primitiveFail]]
+ 			ifFalse: [^ interpreterProxy primitiveFail]].
+ 
+ 	"we don't worry about bitCount"
+ 	"bitCount := 0."
+ 
+ 	"We don't  do - Choose and perform the actual copy loop."
+ 	"self performCopyLoop."
+ 
+ 	"this is done inversely to plain copyBitsLockedAndClipped"
+ 	(combinationRule ~= 22) & (combinationRule ~= 32) ifTrue:
+ 		["zero width and height; return the count"
+ 		affectedL := dx.
+ 		affectedR := dx + bbW.
+ 		affectedT := dy.
+ 		affectedB := dy + bbH].
+ 	
+ 	"Now we fill the 'operation' structure and pass it to the sneaky ARM code"
+ 	self cCode:'
+ 	// fill the operation structure
+ 	operation_t op;
+ 	op.combinationRule = combinationRule;
+ 	op.noSource = noSource;
+ 	op.src.bits = (void *) sourceBits;
+ 	op.src.pitch = sourcePitch;
+ 	op.src.depth = sourceDepth;
+ 	op.src.msb = sourceMSB;
+ 	op.src.x = sx;
+ 	op.src.y = sy;
+ 	op.dest.bits = (void *) destBits;
+ 	op.dest.pitch = destPitch;
+ 	op.dest.depth = destDepth;
+ 	op.dest.msb = destMSB;
+ 	op.dest.x = dx;
+ 	op.dest.y = dy;
+ 	op.width = bbW;
+ 	op.height = bbH;
+ 	op.cmFlags = cmFlags;
+ 	op.cmShiftTable = (void *) cmShiftTable;
+ 	op.cmMaskTable = (void *) cmMaskTable;
+ 	op.cmMask = cmMask;
+ 	op.cmLookupTable = (void *) cmLookupTable;
+ 	op.noHalftone = noHalftone;
+ 	op.halftoneHeight = halftoneHeight;
+ 	op.halftoneBase = (void *) halftoneBase;
+ 	if (combinationRule == 30 || combinationRule == 31) {
+ 		op.opt.sourceAlpha = sourceAlpha;
+ 	}
+ 	if (combinationRule == 41) {
+ 		op.opt.componentAlpha.componentAlphaModeColor = componentAlphaModeColor;
+ 		op.opt.componentAlpha.componentAlphaModeAlpha = componentAlphaModeAlpha;
+ 		op.opt.componentAlpha.gammaLookupTable = (void *) gammaLookupTable;
+ 		op.opt.componentAlpha.ungammaLookupTable = (void *) ungammaLookupTable;
+ 	}
+ 	// call the sneaky code
+ 	copyBitsDispatch(&op)'
+ 	]!

Item was changed:
  ----- Method: BitBltSimulation>>copyBitsLockedAndClipped (in category 'setup') -----
  copyBitsLockedAndClipped
  	"Perform the actual copyBits operation.
  	Assume: Surfaces have been locked and clipping was performed."
+ 	| done |
+ 	<inline: false>
- 	| done gammaLookupTableOop ungammaLookupTableOop |
- 	<inline: true>
- 	"Try a shortcut for stuff that should be run as quickly as possible"
  	
+ 	self copyBitsRule41Test.	
+ 	(interpreterProxy failed not)
+ 		ifFalse: [^ interpreterProxy primitiveFail].
+ 
+  	"Try a shortcut for stuff that should be run as quickly as possible"
+ 	done := self tryCopyingBitsQuickly.
- 	combinationRule = 41
- 		ifTrue:["fetch the forecolor into componentAlphaModeColor."
- 			componentAlphaModeAlpha := 255.
- 			componentAlphaModeColor := 16777215.
- 			gammaLookupTable := nil.
- 			ungammaLookupTable := nil.
- 			interpreterProxy methodArgumentCount >= 2
- 				ifTrue:[
- 					componentAlphaModeAlpha := interpreterProxy stackIntegerValue: (interpreterProxy methodArgumentCount - 2).
- 					(interpreterProxy failed not)
- 						ifFalse: [^ interpreterProxy primitiveFail].
- 					componentAlphaModeColor := interpreterProxy stackIntegerValue: (interpreterProxy methodArgumentCount - 1).
- 					(interpreterProxy failed not)
- 						ifFalse: [^ interpreterProxy primitiveFail].
- 					interpreterProxy methodArgumentCount = 4
- 						ifTrue:[
- 							gammaLookupTableOop := interpreterProxy stackObjectValue: 1.
- 							(interpreterProxy isBytes: gammaLookupTableOop) 
- 								ifTrue:[gammaLookupTable := interpreterProxy firstIndexableField: gammaLookupTableOop.].
- 							ungammaLookupTableOop := interpreterProxy stackObjectValue: 0.
- 							(interpreterProxy isBytes: ungammaLookupTableOop) 
- 								ifTrue:[ungammaLookupTable := interpreterProxy firstIndexableField: ungammaLookupTableOop]]]
- 				ifFalse:[
- 					interpreterProxy methodArgumentCount = 1
- 						ifTrue: [
- 							componentAlphaModeColor := interpreterProxy stackIntegerValue: 0.
- 							(interpreterProxy failed not)
- 								ifFalse: [^ interpreterProxy primitiveFail]]
- 						ifFalse:[^ interpreterProxy primitiveFail]]].	
- 	
-  	done := self tryCopyingBitsQuickly.
  	done ifTrue:[^nil].
  
  	(combinationRule = 30) | (combinationRule = 31) ifTrue:
  		["Check and fetch source alpha parameter for alpha blend"
  		interpreterProxy methodArgumentCount = 1
  			ifTrue: [sourceAlpha := interpreterProxy stackIntegerValue: 0.
  					(interpreterProxy failed not and: [(sourceAlpha >= 0) & (sourceAlpha <= 255)])
  						ifFalse: [^ interpreterProxy primitiveFail]]
  			ifFalse: [^ interpreterProxy primitiveFail]].
  
  	bitCount := 0.
  	"Choose and perform the actual copy loop."
  	self performCopyLoop.
  
  	(combinationRule = 22) | (combinationRule = 32) ifTrue:
  		["zero width and height; return the count"
  		affectedL := affectedR := affectedT := affectedB := 0]. 
  	hDir > 0
  		ifTrue: [affectedL := dx.
  				affectedR := dx + bbW]
  		ifFalse: [affectedL := dx - bbW + 1.
  				affectedR := dx + 1].
  	vDir > 0
  		ifTrue: [affectedT := dy.
  				affectedB := dy + bbH]
  		ifFalse: [affectedT := dy - bbH + 1.
  				affectedB := dy + 1]!

Item was added:
+ ----- Method: BitBltSimulation>>copyBitsRule41Test (in category 'setup') -----
+ copyBitsRule41Test
+ 	"Test possible use of rule 41, rgbComponentAlpha:with: Nothing to return, just set up some variables"
+ 	| gammaLookupTableOop ungammaLookupTableOop |
+ 	<inline: false>
+ 	
+ 	combinationRule = 41
+ 		ifTrue:["fetch the forecolor into componentAlphaModeColor."
+ 			componentAlphaModeAlpha := 255.
+ 			componentAlphaModeColor := 16777215.
+ 			gammaLookupTable := nil.
+ 			ungammaLookupTable := nil.
+ 			interpreterProxy methodArgumentCount >= 2
+ 				ifTrue:[
+ 					componentAlphaModeAlpha := interpreterProxy stackIntegerValue: (interpreterProxy methodArgumentCount - 2).
+ 					(interpreterProxy failed not)
+ 						ifFalse: [^ interpreterProxy primitiveFail].
+ 					componentAlphaModeColor := interpreterProxy stackIntegerValue: (interpreterProxy methodArgumentCount - 1).
+ 					(interpreterProxy failed not)
+ 						ifFalse: [^ interpreterProxy primitiveFail].
+ 					interpreterProxy methodArgumentCount = 4
+ 						ifTrue:[
+ 							gammaLookupTableOop := interpreterProxy stackObjectValue: 1.
+ 							(interpreterProxy isBytes: gammaLookupTableOop) 
+ 								ifTrue:[gammaLookupTable := interpreterProxy firstIndexableField: gammaLookupTableOop.].
+ 							ungammaLookupTableOop := interpreterProxy stackObjectValue: 0.
+ 							(interpreterProxy isBytes: ungammaLookupTableOop) 
+ 								ifTrue:[ungammaLookupTable := interpreterProxy firstIndexableField: ungammaLookupTableOop]]]
+ 				ifFalse:[
+ 					interpreterProxy methodArgumentCount = 1
+ 						ifTrue: [
+ 							componentAlphaModeColor := interpreterProxy stackIntegerValue: 0.
+ 							(interpreterProxy failed not)
+ 								ifFalse: [^ interpreterProxy primitiveFail]]
+ 						ifFalse:[^ interpreterProxy primitiveFail]]].	
+ 
+ 
+ !

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: Cogit>>ceSICMiss: (in category 'in-line cacheing') -----
  ceSICMiss: receiver
  	"An in-line cache check in a method has failed.  The failing entry check has jumped
  	 to the ceMethodAbort abort call at the start of the method which has called this routine.
  	 If possible allocate a closed PIC for the current and existing classes.
  	 The stack looks like:
  			receiver
  			args
  			sender return address
  	  sp=>	ceMethodAbort call return address
  	 So we can find the method that did the failing entry check at
  		ceMethodAbort call return address - missOffset
  	 and we can find the send site from the outer return address."
  	<api>
  	| pic innerReturn outerReturn entryPoint targetMethod newTargetMethodOrNil errorSelectorOrNil cacheTag extent result |
  	<var: #pic type: #'CogMethod *'>
  	<var: #targetMethod type: #'CogMethod *'>
  	"Whether we can relink to a PIC or not we need to pop off the inner return and identify the target method."
  	innerReturn := coInterpreter popStack.
  	targetMethod := self cCoerceSimple: innerReturn - missOffset to: #'CogMethod *'.
  	outerReturn := coInterpreter stackTop.
  	self assert: (outerReturn between: methodZoneBase and: methodZone freeStart).
  	entryPoint := backEnd callTargetFromReturnAddress: outerReturn.
  
  	self assert: targetMethod selector ~= objectMemory nilObject.
  	self cppIf: NewspeakVM ifTrue:
  		[self assert: (targetMethod asInteger + cmEntryOffset = entryPoint
  					or: [targetMethod asInteger + cmDynSuperEntryOffset = entryPoint]).
  		 "Avoid the effort of implementing PICs for the relatively low dynamic frequency
  		  dynamic super send and simply rebind the send site."
  		 targetMethod asInteger + cmDynSuperEntryOffset = entryPoint ifTrue:
  			[^coInterpreter
  				ceDynamicSuperSend: targetMethod selector
  				to: receiver
  				numArgs: targetMethod cmNumArgs]].
  	self assert: targetMethod asInteger + cmEntryOffset = entryPoint.
  
  	self lookup: targetMethod selector
  		for: receiver
  		methodAndErrorSelectorInto:
  			[:method :errsel|
  			newTargetMethodOrNil := method.
  			errorSelectorOrNil := errsel].
  	"We assume lookupAndCog:for: will *not* reclaim the method zone"
  	self assert: outerReturn = coInterpreter stackTop.
  	cacheTag := objectRepresentation inlineCacheTagForInstance: receiver.
  	((errorSelectorOrNil notNil and: [errorSelectorOrNil ~= SelectorDoesNotUnderstand])
  	 or: [(objectRepresentation inlineCacheTagIsYoung: cacheTag)
  	 or: [newTargetMethodOrNil isNil
  	 or: [objectMemory isYoung: newTargetMethodOrNil]]]) ifTrue:
  		[result := self patchToOpenPICFor: targetMethod selector
  					numArgs: targetMethod cmNumArgs
  					receiver: receiver.
  		 self assert: result not. "If patchToOpenPICFor:.. returns we're out of code memory"
  		 ^coInterpreter ceSendFromInLineCacheMiss: targetMethod].
  	"See if an Open PIC is already available."
  	pic := methodZone openPICWithSelector: targetMethod selector.
  	pic isNil ifTrue:
  		["otherwise attempt to create a closed PIC for the two cases."
  		 pic := self cogPICSelector: targetMethod selector
  					numArgs: targetMethod cmNumArgs
  					Case0Method: targetMethod
  					Case1Method: newTargetMethodOrNil
  					tag: cacheTag
  					isMNUCase: errorSelectorOrNil = SelectorDoesNotUnderstand.
+ 		 (pic asInteger between: MaxNegativeErrorCode and: -1) ifTrue:
- 		 pic asInteger < 0 ifTrue:
  			["For some reason the PIC couldn't be generated, most likely a lack of code memory.
  			  Continue as if this is an unlinked send."
  			 pic asInteger = InsufficientCodeSpace ifTrue:
  				[coInterpreter callForCogCompiledCodeCompaction].
  			^coInterpreter ceSendFromInLineCacheMiss: targetMethod].
  		 processor flushICacheFrom: pic asInteger to: pic asInteger + closedPICSize].
  	"Relink the send site to the pic."
  	extent := backEnd
  				rewriteCallAt: outerReturn
  				target: pic asInteger + cmEntryOffset.
  	processor flushICacheFrom: outerReturn - 1 - extent to: outerReturn - 1.
  	"Jump back into the pic at its entry in case this is an MNU (newTargetMethodOrNil is nil)"
  	coInterpreter
  		executeCogMethodFromLinkedSend: pic
  		withReceiver: receiver
  		andCacheTag: (backEnd inlineCacheTagAt: outerReturn).
  	"NOTREACHED"
  	^nil!

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]]!

Item was changed:
  ----- Method: VMMakerTool>>generateSelectedInternalPlugin (in category 'generate sources') -----
  generateSelectedInternalPlugin
  
  	| pluginName |
  	pluginName := self internalModules
+ 						at: self currentInternalModuleIndex
- 						at: self currentExternalModuleIndex
  						ifAbsent: [^self inform: 'no such plugin'].
  	vmMaker interpreterClass
  		ifNil: [^self inform: 'please set an interpreter class']
  		ifNotNil: [:interpreterClass| interpreterClass initialize].
  	self checkOK ifTrue:
  		[[(Smalltalk classNamed: pluginName) touch.
  		  vmMaker generateInternalPlugin: pluginName]
  			on: VMMakerException
  			do: [:ex| self inform: ex messageText]]!



More information about the Vm-dev mailing list