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

commits at source.squeak.org commits at source.squeak.org
Tue Dec 3 03:51:38 UTC 2019


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

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

Name: VMMaker.oscog-eem.2600
Author: eem
Time: 2 December 2019, 7:51:20.659048 pm
UUID: fb9c3e90-4faf-4812-a5a1-2d28197e4a88
Ancestors: VMMaker.oscog-eem.2599

More work for CogARMv8Compiler.  Add register assignments.  Add concretizeLiteral & concretizeMoveRAw.  Hence ceCaptureCStackPointers is now generated.

In-image compilation: Update CurrentImageCoInterpreterFacade now the C stack pointers live in the CoInterpreter.

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

Item was changed:
  ----- Method: CogARMv8Compiler>>computeMaximumSize (in category 'generate machine code') -----
  computeMaximumSize
  	"Because we don't use Thumb, each ARMv8 instruction has 4 bytes. Several
+ 	 abstract opcodes need more than one instruction. Instructions that refer to
+ 	 constants and/or literals depend on literals being stored out-of-line or encoded
+ 	 in immediate instruction fields (i.e. we only support OutOfLineLiteralsManager.
- 	 abstract opcodes need more than one instruction. Instructions that refer
- 	 to constants and/or literals depend on literals being stored in-line or out-of-line.
  
  	 N.B.  The ^N forms are to get around the bytecode compiler's long branch
  	 limits which are exceeded when each case jumps around the otherwise."
  
  	opcode
  		caseOf: {
  		"Noops & Pseudo Ops"
  		[Label]						-> [^0].
+ 		[Literal]						-> [^8].
- 		[Literal]						-> [^4].
  		[AlignmentNops]			-> [^(operands at: 0) - 4].
  		[Fill32]						-> [^4].
  		[Nop]						-> [^4].
  		"Control"
  		[Call]						-> [^4].
  		[CallFull]					-> [^8].
  		[JumpR]					-> [^4].
  		[Jump]						-> [^4].
  		[JumpFull]					-> [^8].
  		[JumpLong]				-> [^4].
  		[JumpZero]					-> [^4].
  		[JumpNonZero]				-> [^4].
  		[JumpNegative]				-> [^4].
  		[JumpNonNegative]			-> [^4].
  		[JumpOverflow]				-> [^4].
  		[JumpNoOverflow]			-> [^4].
  		[JumpCarry]				-> [^4].
  		[JumpNoCarry]				-> [^4].
  		[JumpLess]					-> [^4].
  		[JumpGreaterOrEqual]		-> [^4].
  		[JumpGreater]				-> [^4].
  		[JumpLessOrEqual]			-> [^4].
  		[JumpBelow]				-> [^4].
  		[JumpAboveOrEqual]		-> [^4].
  		[JumpAbove]				-> [^4].
  		[JumpBelowOrEqual]		-> [^4].
  		[JumpLongZero]			-> [^4].
  		[JumpLongNonZero]		-> [^4].
  		[JumpFPEqual]				-> [^8].
  		[JumpFPNotEqual]			-> [^8].
  		[JumpFPLess]				-> [^8].
  		[JumpFPGreaterOrEqual]	-> [^8].
  		[JumpFPGreater]			-> [^8].
  		[JumpFPLessOrEqual]		-> [^8].
  		[JumpFPOrdered]			-> [^8].
  		[JumpFPUnordered]		-> [^8].
  		[RetN]						-> [^(operands at: 0) = 0 ifTrue: [4] ifFalse: [8]].
  		[Stop]						-> [^4].
  
  		"Arithmetic"
+ 		[AddCqR]					-> [^8].
+ 		[AndCqR]					-> [^8].
+ 		[AndCqRR]					-> [^8].
+ 		[CmpCqR]					-> [^8].
+ 		[OrCqR]					-> [^8].
+ 		[SubCqR]					-> [^8].
+ 		[TstCqR]					-> [^8].
+ 		[XorCqR]					-> [^8].
+ 		[AddCwR]					-> [^8].
+ 		[AndCwR]					-> [^8].
+ 		[CmpCwR]					-> [^8].
+ 		[OrCwR]					-> [^8].
+ 		[SubCwR]					-> [^8].
+ 		[XorCwR]					-> [^8].
+ 		[AddRR]					-> [^4].
+ 		[AndRR]					-> [^4].
+ 		[CmpRR]					-> [^4].
+ 		[OrRR]						-> [^4].
+ 		[XorRR]						-> [^4].
+ 		[SubRR]					-> [^4].
+ 		[NegateR]					-> [^4].
+ 		[LoadEffectiveAddressMwrR]-> [^8 halt]. "I think this is likely 4"
- 		[AddCqR]				-> [^8].
- 		[AndCqR]				-> [^8].
- 		[AndCqRR]				-> [^8].
- 		[CmpCqR]				-> [^8].
- 		[OrCqR]				-> [^8].
- 		[SubCqR]				-> [^8].
- 		[TstCqR]				-> [^8].
- 		[XorCqR]				-> [^8].
- 		[AddCwR]				-> [^8].
- 		[AndCwR]				-> [^8].
- 		[CmpCwR]				-> [^8].
- 		[OrCwR]				-> [^8].
- 		[SubCwR]				-> [^8].
- 		[XorCwR]				-> [^8].
- 		[AddRR]				-> [^4].
- 		[AndRR]				-> [^4].
- 		[CmpRR]				-> [^4].
- 		[OrRR]					-> [^4].
- 		[XorRR]					-> [^4].
- 		[SubRR]				-> [^4].
- 		[NegateR]				-> [^4].
- 		[LoadEffectiveAddressMwrR]	-> [8].
  
  		[LogicalShiftLeftCqR]		-> [^4].
  		[LogicalShiftRightCqR]		-> [^4].
  		[ArithmeticShiftRightCqR]	-> [^4].
  		[LogicalShiftLeftRR]			-> [^4].
  		[LogicalShiftRightRR]		-> [^4].
  		[ArithmeticShiftRightRR]	-> [^4].
  		[AddRdRd]					-> [^4].
  		[CmpRdRd]					-> [^4].
  		[SubRdRd]					-> [^4].
  		[MulRdRd]					-> [^4].
  		[DivRdRd]					-> [^4].
  		[SqrtRd]					-> [^4].
  		[ClzRR]						-> [^4].
  		"Data Movement"						
  		[MoveCqR]				-> [^4].
  		[MoveCwR]				-> [^4].
  		[MoveRR]				-> [^4].
  		[MoveRdRd]			-> [^4].
+ 		[MoveAwR]				-> [^((self isAddressRelativeToVarBase: (operands at: 0))
+ 										and: [(operands at: 1) ~= SP])
- 		[MoveAwR]				-> [^(self isAddressRelativeToVarBase: (operands at: 0))
  													ifTrue: [4]
  													ifFalse: [8]].
+ 		[MoveRAw]				-> [^((self isAddressRelativeToVarBase: (operands at: 1))
+ 										and: [(operands at: 0) ~= SP])
- 		[MoveRAw]				-> [^(self isAddressRelativeToVarBase: (operands at: 1))
  													ifTrue: [4]
  													ifFalse: [8]].
  		[MoveAbR]				-> [^(self isAddressRelativeToVarBase: (operands at: 0))
  													ifTrue: [4]
  													ifFalse: [8]].
  		[MoveRAb]				-> [^(self isAddressRelativeToVarBase: (operands at: 1))
  													ifTrue: [4]
  													ifFalse: [8]].
+ 		[MoveMwrR]			-> [^self isPossiblyShiftableImm12: (operands at: 1) ifTrue: [:shift12|4] ifFalse:[8]].
+ 		[MoveRMwr]			-> [^self isPossiblyShiftableImm12: (operands at: 1) ifTrue: [:shift12|4] ifFalse:[8]].
+ 		[MoveMbrR]			-> [^self isPossiblyShiftableImm12: (operands at: 0) ifTrue: [:shift12|4] ifFalse:[8]].
+ 		[MoveRMbr]			-> [^self isPossiblyShiftableImm12: (operands at: 1) ifTrue: [:shift12|4] ifFalse:[8]].
+ 		[MoveM16rR]			-> [^self isPossiblyShiftableImm12: (operands at: 0) ifTrue: [:shift12|4] ifFalse:[8]].
+ 		[MoveRM16r]			-> [^self isPossiblyShiftableImm12: (operands at: 1) ifTrue: [:shift12|4] ifFalse:[8]].
- 		[MoveRMwr]			-> [^self is12BitValue: (operands at: 1)
- 										ifTrue: [:u :i| 4]
- 										ifFalse: [8]].
- 		[MoveRdM64r]			-> [^8]. 
- 		[MoveMbrR]			-> [^self is12BitValue: (operands at: 0)
- 										ifTrue: [:u :i| 4]
- 										ifFalse: [8]].
- 		[MoveRMbr]			-> [^self is12BitValue: (operands at: 1)
- 										ifTrue: [:u :i| 4]
- 										ifFalse: [8]].
- 		[MoveRM16r]			-> [^self is12BitValue: (operands at: 1)
- 										ifTrue: [:u :i| 4]
- 										ifFalse: [8]].
- 		[MoveM16rR]			-> [self halt].
  		[MoveM64rRd]			-> [^8].
+ 		[MoveRdM64r]			-> [^8].
- 		[MoveMwrR]			-> [^self is12BitValue: (operands at: 0)
- 										ifTrue: [:u :i| 4]
- 										ifFalse: [8]].
  		[MoveXbrRR]			-> [^4].
  		[MoveRXbrR]			-> [^4].
  		[MoveXwrRR]			-> [^4].
  		[MoveRXwrR]			-> [^4].
  		[PopR]					-> [^4].
  		[PushR]					-> [^4].
  		[PushCw]				-> [self halt].
  		[PushCq]				-> [self halt].
  		[PrefetchAw] 			-> [self halt].
  		"Conversion"
  		[ConvertRRd]			-> [^8].
  		}.
  	^0 "to keep C compiler quiet"
  !

Item was added:
+ ----- Method: CogARMv8Compiler>>concretizeLiteral (in category 'generate machine code') -----
+ concretizeLiteral
+ 	"Generate an out-of-line literal.  Copy the value and any annotation from the stand-in in the literals manager."
+ 	| literalAsInstruction literal |
+ 	<var: 'literal' type: #usqInt>
+ 	literalAsInstruction := cogit cCoerceSimple: (operands at: 0) to: #'AbstractInstruction *'.
+ 	literal := (self isAnInstruction: literalAsInstruction)
+ 				ifTrue: [literalAsInstruction address]
+ 				ifFalse: [self cCode: [literalAsInstruction asUnsignedInteger]
+ 							inSmalltalk: [literalAsInstruction]].
+ 	self assert: (dependent notNil and: [dependent opcode = Literal]).
+ 	dependent annotation ifNotNil:
+ 		[self assert: annotation isNil.
+ 		 annotation := dependent annotation].
+ 	dependent address ifNotNil: [self assert: dependent address = address].
+ 	dependent address: address.
+ 	machineCode
+ 		at: 0 put: (literal bitAnd: 16rFFFFFFFF);
+ 		at: 1 put: (literal >> 32).
+ 	machineCodeSize := 8!

Item was added:
+ ----- Method: CogARMv8Compiler>>concretizeMoveRAw (in category 'generate machine code - concretize') -----
+ concretizeMoveRAw
+ 	"Will get inlined into concretizeAt: switch."
+ 	<inline: true>
+ 	| srcReg destAddr instrOffset|
+ 	srcReg := operands at: 0.
+ 	destAddr := operands at: 1.
+ 	"str srcReg, [VarBaseReg, #offset] except that this is illegal for SP/X31"
+ 	(self isAddressRelativeToVarBase: destAddr) ifTrue:
+ 		[destAddr < cogit varBaseAddress ifTrue:
+ 			[self shouldBeImplemented.
+ 			 ^machineCodeSize := 4].
+ 		 srcReg ~= SP ifTrue:
+ 			[machineCode
+ 				at: 0
+ 				put: (self strn: srcReg rt: VarBaseReg imm: destAddr - cogit varBaseAddress shiftBy12: false).
+ 			 ^machineCodeSize := 4].
+ 		machineCode
+ 			at: 0
+ 			put: (self movern: srcReg rd: RISCTempReg);
+ 			at: 1
+ 			put: (self strn: RISCTempReg rt: VarBaseReg imm: destAddr - cogit varBaseAddress shiftBy12: false).
+ 		^machineCodeSize := 8].
+ 	"LEA ConcreteIPReg
+ 	 str srcReg, [ConcreteIPReg]"
+ 	instrOffset := self moveCw: destAddr intoR: RISCTempReg.
+ 	machineCode
+ 		at: instrOffset // 4
+ 		put: (self strn: srcReg rt: RISCTempReg imm: 0 shiftBy12: false).
+ 	^machineCodeSize := instrOffset + 4!

Item was added:
+ ----- Method: CogARMv8Compiler>>isAddressRelativeToVarBase: (in category 'testing') -----
+ isAddressRelativeToVarBase: varAddress
+ 	<inline: true>
+ 	<var: #varAddress type: #usqInt>
+ 	"Support for addressing variables off the dedicated VarBaseReg"
+ 	^varAddress notNil
+ 	  and: [varAddress
+ 				between: cogit varBaseAddress - (1 << 8)
+ 				and: cogit varBaseAddress + (1 << 12) - 1]!

Item was added:
+ ----- Method: CogARMv8Compiler>>isPossiblyShiftableImm12:ifTrue:ifFalse: (in category 'generate machine code - support') -----
+ isPossiblyShiftableImm12: immediate ifTrue: unaryBlock ifFalse: nullaryBlock
+ 	<inline: #always>
+ 	(immediate between: 0 and: 1 << 12 - 1) ifTrue:
+ 		[^unaryBlock value: false].
+ 	((immediate noMask: 1 << 12 - 1)
+ 	 and: [immediate >> 12 between: 0 and: 1 << 12 - 1]) ifTrue:
+ 		[^unaryBlock value: true].
+ 	^nullaryBlock value!

Item was added:
+ ----- Method: CogARMv8Compiler>>isPossiblyShiftableImm12orImm9:ifTrue:ifFalse: (in category 'generate machine code - support') -----
+ isPossiblyShiftableImm12orImm9: immediate ifTrue: unaryBlock ifFalse: nullaryBlock
+ 	<inline: #always>
+ 	((immediate between: -256 and: 255)
+ 	 or: [immediate between: 0 and: 1 << 12 - 1]) ifTrue:
+ 		[^unaryBlock value: false].
+ 	((immediate noMask: 1 << 12 - 1)
+ 	 and: [immediate >> 12 between: 0 and: 1 << 12 - 1]) ifTrue:
+ 		[^unaryBlock value: true].
+ 	^nullaryBlock value!

Item was added:
+ ----- Method: CogARMv8Compiler>>isSharable (in category 'generate machine code') -----
+ isSharable
+ 	"Hack:  To know if a literal should be unique (not shared) mark the second operand."
+ 	<inline: true>
+ 	self assert: opcode = Literal.
+ 	^operands at: 1!

Item was added:
+ ----- Method: CogARMv8Compiler>>literalOpcodeIndex (in category 'generate machine code') -----
+ literalOpcodeIndex
+ 	"Hack:  To know how far away a literal is from its referencing instruction we store
+ 	 its opcodeIndex, or -1, if as yet unassigned, in the second operand of the literal."
+ 	<inline: true>
+ 	self assert: opcode = Literal.
+ 	^(operands at: 2) asInteger!

Item was added:
+ ----- Method: CogARMv8Compiler>>moveCw:intoR: (in category 'generate machine code - support') -----
+ moveCw: constant intoR: destReg
+ 	"Emit a load of aWord into destReg.  Answer the number of bytes of machine code generated.
+ 	 Literals are stored out-of-line; emit a LDR with the relevant offset."
+ 	 <var: 'constant' type: #usqInt>
+ 	<inline: true>
+ 	self assert: (cogit addressIsInCurrentCompilation: dependent address).
+ 	self assert: (dependent address bitAnd: 3) = 0.
+ 	self assert: (dependent address - address) abs < (1<<19).
+ 	"C6.2.131	LDR (literal)		C6-979"
+ 	machineCode
+ 		at: 0
+ 		put: 2r01011000 << 24
+ 			+ destReg
+ 			+ ((dependent address - (address + 8) bitAnd: 1 << 19 - 1) << 5).
+ 	^machineCodeSize := 4!

Item was added:
+ ----- Method: CogARMv8Compiler>>movern:rd: (in category 'generate machine code - support') -----
+ movern: srcReg rd: destReg
+ 	^self addrn: srcReg rd: destReg imm: 0 shiftBy12: false!

Item was added:
+ ----- Method: CogARMv8Compiler>>setLiteralOpcodeIndex: (in category 'generate machine code') -----
+ setLiteralOpcodeIndex: index
+ 	"Hack:  To know how far away a literal is from its referencing instruction we store
+ 	 its opcodeIndex, or -1, if as yet unassigned, in the second operand of the literal."
+ 	<inline: true>
+ 	self assert: opcode = Literal.
+ 	operands at: 2 put: index!

Item was added:
+ ----- Method: CogARMv8Compiler>>strn:rt:imm:shiftBy12: (in category 'generate machine code - support') -----
+ strn: srcReg rt: targetReg imm: offset shiftBy12: shiftBy12
+ 	"C6.2.273	STR (immediate)	C6-1239
+ 	 C6.2.297	STUR				C6-1290"
+ 
+ 	self deny: srcReg = SP.
+ 	"Unsigned offset, C6-1240"
+ 	(offset \\ 8 = 0
+ 	 and: [offset / 8 between: 0 and: 1 << 12 - 1]) ifTrue:
+ 		[^2r1111100100 << 22
+ 		+ (offset << 7 "10 - 3")
+ 		+ (targetReg << 5)
+ 		+ srcReg].
+ 	self assert: (offset between: -256 and: 255).
+ 	^2r11111000000 << 21
+ 	  + ((offset bitAnd: 511) << 12)
+ 	  + (targetReg << 5)
+ 	  + srcReg!

Item was added:
+ ----- Method: CogARMv8Compiler>>usesOutOfLineLiteral (in category 'testing') -----
+ usesOutOfLineLiteral
+ 	"Answer if the receiver uses an out-of-line literal.  Needs only
+ 	 to work for the opcodes created with gen:literal:operand: et al."
+ 
+ 	opcode
+ 		caseOf: {
+ 		[CallFull]		-> [^true].
+ 		[JumpFull]		-> [^true].
+ 		"Arithmetic"
+ 		[AddCqR]		-> [^self isPossiblyShiftableImm12: (operands at: 0) ifTrue: [:shift12|false] ifFalse:[true]].
+ 		[AndCqR]		-> [^self isPossiblyShiftableImm12: (operands at: 0) ifTrue: [:shift12|false] ifFalse:[true]].
+ 		[AndCqRR]		-> [^self isPossiblyShiftableImm12: (operands at: 0) ifTrue: [:shift12|false] ifFalse:[true]].
+ 		[CmpCqR]		-> [^self isPossiblyShiftableImm12: (operands at: 0) ifTrue: [:shift12|false] ifFalse:[true]].
+ 		[OrCqR]		-> [^self isPossiblyShiftableImm12: (operands at: 0) ifTrue: [:shift12|false] ifFalse:[true]].
+ 		[SubCqR]		-> [^self isPossiblyShiftableImm12: (operands at: 0) ifTrue: [:shift12|false] ifFalse:[true]].
+ 		[TstCqR]		-> [^self isPossiblyShiftableImm12: (operands at: 0) ifTrue: [:shift12|false] ifFalse:[true]].
+ 		[XorCqR]		-> [^self isPossiblyShiftableImm12: (operands at: 0) ifTrue: [:shift12|false] ifFalse:[true]].
+ 		[AddCwR]		-> [^true].
+ 		[AndCwR]		-> [^true].
+ 		[CmpCwR]		-> [^true].
+ 		[OrCwR]		-> [^true].
+ 		[SubCwR]		-> [^true].
+ 		[XorCwR]		-> [^true].
+ 		"[LoadEffectiveAddressMwrR]
+ 						-> [^self rotateable8bitImmediate: (operands at: 0) ifTrue: [:r :i| false] ifFalse: [true]]."
+ 		"Data Movement"						
+ 		"[MoveCqR]		-> [^self rotateable8bitImmediate: (operands at: 0) ifTrue: [:r :i| false] ifFalse: [true]]."
+ 		[MoveCwR]		-> [^(self inCurrentCompilation: (operands at: 0)) not].
+ 		[MoveAwR]		-> [^(self isAddressRelativeToVarBase: (operands at: 0)) not].
+ 		[MoveRAw]		-> [^(self isAddressRelativeToVarBase: (operands at: 1)) not].
+ 		[MoveAbR]		-> [^(self isAddressRelativeToVarBase: (operands at: 0)) not].
+ 		[MoveRAb]		-> [^(self isAddressRelativeToVarBase: (operands at: 1)) not].
+ 		[MoveMwrR]	-> [^self isPossiblyShiftableImm12orImm9: (operands at: 0) ifTrue: [:shift12|false] ifFalse:[true]].
+ 		[MoveRMwr]	-> [^self isPossiblyShiftableImm12orImm9: (operands at: 1) ifTrue: [:shift12|false] ifFalse:[true]].
+ 		[MoveMbrR]	-> [^self isPossiblyShiftableImm12orImm9: (operands at: 0) ifTrue: [:shift12|false] ifFalse:[true]].
+ 		[MoveRMbr]	-> [^self isPossiblyShiftableImm12orImm9: (operands at: 1) ifTrue: [:shift12|false] ifFalse:[true]].
+ 		[MoveM16rR]	-> [^self isPossiblyShiftableImm12orImm9: (operands at: 0) ifTrue: [:shift12|false] ifFalse:[true]].
+ 		[MoveRM16r]	-> [^self isPossiblyShiftableImm12orImm9: (operands at: 1) ifTrue: [:shift12|false] ifFalse:[true]].
+ 		"[MoveRdM64r]	-> [^self is12BitValue: (operands at: 1) ifTrue: [:u :i| false] ifFalse: [true]].
+ 		[MoveM64rRd]	-> [^self is12BitValue: (operands at: 0) ifTrue: [:u :i| false] ifFalse: [true]]."
+ 		[PushCw]		-> [^(self inCurrentCompilation: (operands at: 0)) not].
+ 		"[PushCq]		-> [^self rotateable8bitImmediate: (operands at: 0) ifTrue: [:r :i| false] ifFalse: [true]]."
+ 		[PrefetchAw] 	-> [^(self isAddressRelativeToVarBase: (operands at: 0)) not].
+ 		}
+ 		otherwise: [self assert: false].
+ 	^false "to keep C compiler quiet"
+ !

Item was changed:
  CogClass subclass: #CurrentImageCoInterpreterFacade
+ 	instanceVariableNames: 'memory cogit coInterpreter objectMemory objectMap headerToMethodMap cachedObject cachedOop variables cFramePointer cStackPointer'
- 	instanceVariableNames: 'memory cogit coInterpreter objectMemory objectMap headerToMethodMap cachedObject cachedOop variables'
  	classVariableNames: ''
  	poolDictionaries: 'CogMethodConstants VMBasicConstants VMObjectIndices VMSqueakClassIndices'
  	category: 'VMMaker-Support'!
  
  !CurrentImageCoInterpreterFacade commentStamp: 'eem 8/6/2014 14:59' prior: 0!
  A CurrentImageCoInterpreterFacade is a stand-in for an object memory (ObjectMemory, SpurMemoryManager, etc) that allows the Cogits to access image objects as if they were in the simulator VM's heap.  hence it allows the Cogits to generate code for methdos in the current image, for testing, etc.
  
  Instance Variables
  	cachedObject:			<Object>
  	cachedOop:			<Integer>
  	coInterpreter:			<CoInterpreter>
  	cogit:					<Cogit>
  	headerToMethodMap:	<Dictionary>
  	memory:				<ByteArray>
  	objectMap:				<IdentityDictionary>
  	objectMemory:			<NewObjectMemory|SpurMemoryManager>
  	variables:				<Dictionary>
  
  cachedObject
  	- the object matching cachedOop, to speed-up oop to obejct mapping
  
  cachedOop
  	- the last used oop
  
  coInterpreter
  	- the CoInterpreter simulator used by the cogit.
  
  cogit
  	- the code egnerator in use
  
  headerToMethodMap
  	- a map from header to CompiledMethod
  
  memory
  	- a rump memory for holding various interpreter variables (e.g. stackLimit) that are accessed as memory locations by generated code
  
  objectMap
  	- map from objects to their oops
  
  objectMemory
  	- the object memory used to encode various values, answer queries, etc
  
  variables
  	- a map from the names of variables to their addresses in memory
  !

Item was added:
+ ----- Method: CurrentImageCoInterpreterFacade>>checkIfCFramePointerInUse (in category 'cog jit support') -----
+ checkIfCFramePointerInUse
+ 	^true!

Item was added:
+ ----- Method: CurrentImageCoInterpreterFacade>>setCFramePointer:setCStackPointer: (in category 'cog jit support') -----
+ setCFramePointer: fp setCStackPointer: sp
+ 	cFramePointer := fp.
+ 	cStackPointer := sp!



More information about the Vm-dev mailing list