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

commits at source.squeak.org commits at source.squeak.org
Wed Nov 4 16:40:42 UTC 2015


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

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

Name: VMMaker.oscog-eem.1508
Author: eem
Time: 4 November 2015, 8:38:48.263 am
UUID: 4d5233a4-5fe7-4211-8e7d-d4b3e4ed4fec
Ancestors: VMMaker.oscog-eem.1507

x64 Cogit:

Refactor some instantiation routines in the Spur object representation to use the header initialization abstraction.

Add instruction sizing to allow disassembly of methods containing blocks.

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

Item was added:
+ ----- Method: CogAbstractInstruction>>instructionSizeAt: (in category 'disassembly') -----
+ instructionSizeAt: pc
+ 	"Answer the instruction size at pc. This is used in method disassembly
+ 	 to decode the jumps in block dispatch to discover where block methods
+ 	 occur within a larger method."
+ 	^4!

Item was added:
+ ----- Method: CogObjectRepresentationFor32BitSpur>>genLoadHeader:intoNewInstance:using: (in category 'initialization') -----
+ genLoadHeader: header intoNewInstance: rcvrReg using: scratchReg
+ 	"Generate the instructions to move the constant header into a new instance pointed to by rcvrReg."
+ 	<inline: true>
+ 	self flag: #endianness.
+ 	cogit
+ 		MoveCq: (self low32BitsOf: header) R: scratchReg;
+ 		MoveR: scratchReg Mw: 0 r: rcvrReg;
+ 		MoveCq: header >> 32 R: scratchReg;
+ 		MoveR: scratchReg Mw: 4 r: rcvrReg!

Item was removed:
- ----- Method: CogObjectRepresentationFor32BitSpur>>genLoadHeaderIntoNewInstance: (in category 'initialization') -----
- genLoadHeaderIntoNewInstance: header
- 	"Generate the instructions to move the constant header into a new instance pointed to by ReceiverResultReg."
- 	<inline: true>
- 	self flag: #endianness.
- 	cogit
- 		MoveCq: (self low32BitsOf: header) R: TempReg;
- 		MoveR: TempReg Mw: 0 r: ReceiverResultReg;
- 		MoveCq: header >> 32 R: TempReg;
- 		MoveR: TempReg Mw: 4 r: ReceiverResultReg!

Item was removed:
- ----- Method: CogObjectRepresentationFor32BitSpur>>genNewArrayOfSize:initialized: (in category 'bytecode generator support') -----
- genNewArrayOfSize: size initialized: initialized
- 	"Generate a call to code that allocates a new Array of size.
- 	 The Array should be initialized with nils iff initialized is true.
- 	 The size arg is passed in SendNumArgsReg, the result
- 	 must come back in ReceiverResultReg."
- 	| header skip |
- 	<var: #skip type: #'AbstractInstruction *'>
- 	self assert: size < objectMemory numSlotsMask.
- 	header := objectMemory
- 					headerForSlots: size
- 					format: objectMemory arrayFormat
- 					classIndex: ClassArrayCompactIndex.
- 	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.
- 	(initialized and: [size > 0]) ifTrue:
- 		[cogit genMoveConstant: objectMemory nilObject R: TempReg.
- 		 1 to: size do:
- 			[:i| cogit MoveR: TempReg Mw: i * 4 + 4 r: ReceiverResultReg]].
- 	cogit
- 		MoveR: ReceiverResultReg R: TempReg;
- 		AddCq: (objectMemory smallObjectBytesForSlots: size) R: TempReg;
- 		MoveR: TempReg Aw: objectMemory freeStartAddress;
- 		CmpCq: objectMemory getScavengeThreshold R: TempReg.
- 	skip := cogit JumpBelow: 0.
- 	cogit CallRT: ceScheduleScavengeTrampoline.
- 	skip jmpTarget: cogit Label.
- 	^0!

Item was removed:
- ----- Method: CogObjectRepresentationFor32BitSpur>>genNoPopCreateClosureAt:numArgs:numCopied:contextNumArgs:large:inBlock: (in category 'bytecode generator support') -----
- genNoPopCreateClosureAt: bcpc numArgs: numArgs numCopied: numCopied contextNumArgs: ctxtNumArgs large: isLargeCtxt inBlock: isInBlock
- 	"Create a closure with the given startpc, numArgs and numCopied
- 	 within a context with ctxtNumArgs, large if isLargeCtxt that is in a
- 	 block if isInBlock.  Do /not/ initialize the copied values."
- 	| numSlots byteSize header skip |
- 	<var: #skip type: #'AbstractInstruction *'>
- 
- 	"First get thisContext into ReceiverResultRega and thence in ClassReg."
- 	self genGetActiveContextNumArgs: ctxtNumArgs large: isLargeCtxt inBlock: isInBlock.
- 	cogit MoveR: ReceiverResultReg R: ClassReg.
- 
- 	numSlots := ClosureFirstCopiedValueIndex + numCopied.
- 	byteSize := objectMemory smallObjectBytesForSlots: numSlots.
- 	header := objectMemory
- 					headerForSlots: numSlots
- 					format: objectMemory indexablePointersFormat
- 					classIndex: ClassBlockClosureCompactIndex.
- 	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;
- 		LoadEffectiveAddressMw: byteSize r: ReceiverResultReg R: TempReg;
- 		MoveR: TempReg Aw: objectMemory freeStartAddress;
- 		CmpCq: objectMemory getScavengeThreshold R: TempReg.
- 	skip := cogit JumpBelow: 0.
- 	cogit CallRT: ceScheduleScavengeTrampoline.
- 	skip jmpTarget: cogit Label.
- 
- 	cogit
- 		MoveR: ClassReg Mw: ClosureOuterContextIndex * objectMemory bytesPerOop + objectMemory baseHeaderSize r: ReceiverResultReg;
- 		MoveCq: (objectMemory integerObjectOf: bcpc) R: TempReg;
- 		MoveR: TempReg Mw: ClosureStartPCIndex * objectMemory bytesPerOop + objectMemory baseHeaderSize r: ReceiverResultReg;
- 		MoveCq: (objectMemory integerObjectOf: numArgs) R: TempReg;
- 		MoveR: TempReg Mw: ClosureNumArgsIndex * objectMemory bytesPerOop + objectMemory baseHeaderSize r: ReceiverResultReg.
- 	^0!

Item was added:
+ ----- Method: CogObjectRepresentationFor64BitSpur>>genLoadHeader:intoNewInstance:using: (in category 'initialization') -----
+ genLoadHeader: header intoNewInstance: rcvrReg using: scratchReg
+ 	"Generate the instructions to move the constant header into a new instance pointed to by rcvrReg."
+ 	<inline: true>
+ 	cogit
+ 		MoveCq: header R: scratchReg;
+ 		MoveR: TempReg Mw: 0 r: rcvrReg!

Item was removed:
- ----- Method: CogObjectRepresentationFor64BitSpur>>genLoadHeaderIntoNewInstance: (in category 'initialization') -----
- genLoadHeaderIntoNewInstance: header
- 	"Generate the instructions to move the constant header into a new instance pointed to by ReceiverResultReg."
- 	<inline: true>
- 	self flag: #endianness.
- 	cogit
- 		MoveCq: header R: TempReg;
- 		MoveR: TempReg Mw: 0 r: ReceiverResultReg!

Item was removed:
- ----- Method: CogObjectRepresentationFor64BitSpur>>genNoPopCreateClosureAt:numArgs:numCopied:contextNumArgs:large:inBlock: (in category 'bytecode generator support') -----
- genNoPopCreateClosureAt: bcpc numArgs: numArgs numCopied: numCopied contextNumArgs: ctxtNumArgs large: isLargeCtxt inBlock: isInBlock
- 	"Create a closure with the given startpc, numArgs and numCopied
- 	 within a context with ctxtNumArgs, large if isLargeCtxt that is in a
- 	 block if isInBlock.  Do /not/ initialize the copied values."
- 	| numSlots byteSize header skip |
- 	<var: #skip type: #'AbstractInstruction *'>
- 
- 	"First get thisContext into ReceiverResultRega and thence in ClassReg."
- 	self genGetActiveContextNumArgs: ctxtNumArgs large: isLargeCtxt inBlock: isInBlock.
- 	cogit MoveR: ReceiverResultReg R: ClassReg.
- 
- 	numSlots := ClosureFirstCopiedValueIndex + numCopied.
- 	byteSize := objectMemory smallObjectBytesForSlots: numSlots.
- 	header := objectMemory
- 					headerForSlots: numSlots
- 					format: objectMemory indexablePointersFormat
- 					classIndex: ClassBlockClosureCompactIndex.
- 	cogit
- 		MoveAw: objectMemory freeStartAddress R: ReceiverResultReg;
- 		MoveCq: header R: TempReg;
- 		MoveR: TempReg Mw: 0 r: ReceiverResultReg;
- 		LoadEffectiveAddressMw: byteSize r: ReceiverResultReg R: TempReg;
- 		MoveR: TempReg Aw: objectMemory freeStartAddress;
- 		CmpCq: objectMemory getScavengeThreshold R: TempReg.
- 	skip := cogit JumpBelow: 0.
- 	cogit CallRT: ceScheduleScavengeTrampoline.
- 	skip jmpTarget: cogit Label.
- 
- 	cogit
- 		MoveR: ClassReg Mw: ClosureOuterContextIndex * objectMemory bytesPerOop + objectMemory baseHeaderSize r: ReceiverResultReg;
- 		MoveCq: (objectMemory integerObjectOf: bcpc) R: TempReg;
- 		MoveR: TempReg Mw: ClosureStartPCIndex * objectMemory bytesPerOop + objectMemory baseHeaderSize r: ReceiverResultReg;
- 		MoveCq: (objectMemory integerObjectOf: numArgs) R: TempReg;
- 		MoveR: TempReg Mw: ClosureNumArgsIndex * objectMemory bytesPerOop + objectMemory baseHeaderSize r: ReceiverResultReg.
- 	^0!

Item was changed:
  ----- Method: CogObjectRepresentationForSpur>>genAllocFloatValue:into:scratchReg:scratchReg: (in category 'primitive generators') -----
  genAllocFloatValue: dpreg into: resultReg scratchReg: scratch1 scratchReg: scratch2
  	<returnTypeC: #'AbstractInstruction *'>
  	| allocSize newFloatHeader jumpFail |
  	<var: #jumpFail type: #'AbstractInstruction *'>
  	allocSize := objectMemory baseHeaderSize + (objectMemory sizeof: #double).
  	newFloatHeader := objectMemory
  							headerForSlots: (self sizeof: #double) / objectMemory wordSize
  							format: objectMemory firstLongFormat
  							classIndex: ClassFloatCompactIndex.
  	cogit MoveAw: objectMemory freeStartAddress R: resultReg.
  	cogit LoadEffectiveAddressMw: allocSize r: resultReg R: scratch1.
  	cogit CmpCq: objectMemory getScavengeThreshold R: scratch1.
  	jumpFail := cogit JumpAboveOrEqual: 0.
  	cogit MoveR: scratch1 Aw: objectMemory freeStartAddress.
+ 	self genLoadHeader: newFloatHeader intoNewInstance: resultReg using: scratch1.
- 	cogit MoveCq: newFloatHeader R: scratch2.
- 	objectMemory wordSize = objectMemory baseHeaderSize
- 		ifTrue: [cogit MoveR: scratch2 Mw: 0 r: resultReg]
- 		ifFalse:
- 			[self flag: #endianness.
- 			 cogit MoveCq: newFloatHeader >> 32 R: scratch1.
- 			 cogit MoveR: scratch2 Mw: 0 r: resultReg.
- 			 cogit MoveR: scratch1 Mw: objectMemory wordSize r: resultReg].
  	cogit MoveRd: dpreg M64: objectMemory baseHeaderSize r: resultReg.
  	^jumpFail!

Item was changed:
  ----- Method: CogObjectRepresentationForSpur>>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.
+ 	self genLoadHeader: header intoNewInstance: ReceiverResultReg using: TempReg.
- 	self genLoadHeaderIntoNewInstance: header.
  	cogit
  		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 - wordSize (1 each for saved pc, method, context, receiver) + 1 (1-relative) + numArgs"
  	"TPR note - the code here is actually doing
  	context stackPointer := ((((fp - sp) / wordSize) - [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 genMoveConstant: 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) * wordSize)). +2 for saved pc and savedfp
  		longAtput(FPReg + FoxMFReceiver + (i * wordSize), 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 - wordSize.
  	  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].
  	cogit Jump: continuation.
  	^0!

Item was added:
+ ----- Method: CogObjectRepresentationForSpur>>genLoadHeader:intoNewInstance:using: (in category 'initialization') -----
+ genLoadHeader: header intoNewInstance: rcvrReg using: scratchReg
+ 	"Generate the instructions to move the constant header into a new instance pointed to by rcvrReg."
+ 	<inline: true>
+ 	self subclassResponsibility!

Item was removed:
- ----- Method: CogObjectRepresentationForSpur>>genLoadHeaderIntoNewInstance: (in category 'initialization') -----
- genLoadHeaderIntoNewInstance: header
- 	"Generate the instructions to move the constant header into a new instance pointed to by ReceiverResultReg."
- 	^self subclassResponsibility!

Item was added:
+ ----- Method: CogObjectRepresentationForSpur>>genNewArrayOfSize:initialized: (in category 'bytecode generator support') -----
+ genNewArrayOfSize: size initialized: initialized
+ 	"Generate a call to code that allocates a new Array of size.
+ 	 The Array should be initialized with nils iff initialized is true.
+ 	 The size arg is passed in SendNumArgsReg, the result
+ 	 must come back in ReceiverResultReg."
+ 	| header skip |
+ 	<var: #skip type: #'AbstractInstruction *'>
+ 	self assert: size < objectMemory numSlotsMask.
+ 	header := objectMemory
+ 					headerForSlots: size
+ 					format: objectMemory arrayFormat
+ 					classIndex: ClassArrayCompactIndex.
+ 	cogit MoveAw: objectMemory freeStartAddress R: ReceiverResultReg.
+ 	self genLoadHeader: header intoNewInstance: ReceiverResultReg using: TempReg.
+ 	(initialized and: [size > 0]) ifTrue:
+ 		[cogit genMoveConstant: objectMemory nilObject R: TempReg.
+ 		 0 to: size - 1 do:
+ 			[:i| cogit MoveR: TempReg
+ 					Mw: i * objectMemory wordSize + objectMemory baseHeaderSize
+ 					r: ReceiverResultReg]].
+ 	cogit
+ 		LoadEffectiveAddressMw: (objectMemory smallObjectBytesForSlots: size) r: ReceiverResultReg R: TempReg;
+ 		MoveR: TempReg Aw: objectMemory freeStartAddress;
+ 		CmpCq: objectMemory getScavengeThreshold R: TempReg.
+ 	skip := cogit JumpBelow: 0.
+ 	cogit CallRT: ceScheduleScavengeTrampoline.
+ 	skip jmpTarget: cogit Label.
+ 	^0!

Item was added:
+ ----- Method: CogObjectRepresentationForSpur>>genNoPopCreateClosureAt:numArgs:numCopied:contextNumArgs:large:inBlock: (in category 'bytecode generator support') -----
+ genNoPopCreateClosureAt: bcpc numArgs: numArgs numCopied: numCopied contextNumArgs: ctxtNumArgs large: isLargeCtxt inBlock: isInBlock
+ 	"Create a closure with the given startpc, numArgs and numCopied
+ 	 within a context with ctxtNumArgs, large if isLargeCtxt that is in a
+ 	 block if isInBlock.  Do /not/ initialize the copied values."
+ 	| numSlots byteSize header skip |
+ 	<var: #skip type: #'AbstractInstruction *'>
+ 
+ 	"First get thisContext into ReceiverResultRega and thence in ClassReg."
+ 	self genGetActiveContextNumArgs: ctxtNumArgs large: isLargeCtxt inBlock: isInBlock.
+ 	cogit MoveR: ReceiverResultReg R: ClassReg.
+ 
+ 	numSlots := ClosureFirstCopiedValueIndex + numCopied.
+ 	byteSize := objectMemory smallObjectBytesForSlots: numSlots.
+ 	header := objectMemory
+ 					headerForSlots: numSlots
+ 					format: objectMemory indexablePointersFormat
+ 					classIndex: ClassBlockClosureCompactIndex.
+ 	cogit MoveAw: objectMemory freeStartAddress R: ReceiverResultReg.
+ 	self genLoadHeader: header intoNewInstance: ReceiverResultReg using: TempReg.
+ 	cogit
+ 		LoadEffectiveAddressMw: byteSize r: ReceiverResultReg R: TempReg;
+ 		MoveR: TempReg Aw: objectMemory freeStartAddress;
+ 		CmpCq: objectMemory getScavengeThreshold R: TempReg.
+ 	skip := cogit JumpBelow: 0.
+ 	cogit CallRT: ceScheduleScavengeTrampoline.
+ 	skip jmpTarget: cogit Label.
+ 
+ 	cogit
+ 		MoveR: ClassReg Mw: ClosureOuterContextIndex * objectMemory bytesPerOop + objectMemory baseHeaderSize r: ReceiverResultReg;
+ 		MoveCq: (objectMemory integerObjectOf: bcpc) R: TempReg;
+ 		MoveR: TempReg Mw: ClosureStartPCIndex * objectMemory bytesPerOop + objectMemory baseHeaderSize r: ReceiverResultReg;
+ 		MoveCq: (objectMemory integerObjectOf: numArgs) R: TempReg;
+ 		MoveR: TempReg Mw: ClosureNumArgsIndex * objectMemory bytesPerOop + objectMemory baseHeaderSize r: ReceiverResultReg.
+ 	^0!

Item was added:
+ ----- Method: CogX64Compiler>>instructionSizeAt: (in category 'disassembly') -----
+ instructionSizeAt: pc
+ 	"Answer the instruction size at pc. This is used in method disassembly
+ 	 to decode the jumps in block dispatch to discover where block methods
+ 	 occur within a larger method.   This is very far from a full decode."
+ 	| op |
+ 	op := objectMemory byteAt: pc.
+ 	(op bitAnd: 16rF8) = 16r48 ifTrue:
+ 		[^1 + (self instructionSizeAt: pc + 1)].
+ 	^op caseOf:
+ 		{	[16r0F]	->	[self twoByteInstructionSizeAt: pc].
+ 			[16r3D]	->	[5]. "cmp EAX,imm32"
+ 			[16r70]	->	[2]. "short conditional jumps"
+ 			[16r71]	->	[2].
+ 			[16r72]	->	[2].
+ 			[16r73]	->	[2].
+ 			[16r74]	->	[2].
+ 			[16r75]	->	[2].
+ 			[16r76]	->	[2].
+ 			[16r77]	->	[2].
+ 			[16r78]	->	[2].
+ 			[16r79]	->	[2].
+ 			[16r7A]	->	[2].
+ 			[16r7B]	->	[2].
+ 			[16r7C]	->	[2].
+ 			[16r7D]	->	[2].
+ 			[16r7E]	->	[2].
+ 			[16r7F]	->	[2].
+ 			[16r83]	->	[self sizeImmediateGroup1: op at: pc].
+ 			[16r89]	->	[2]. "MOV Eb,Gb"
+ 			[16r8B]	->	[self sizeHasModrm: op at: pc].
+ 			[16r90]	->	[1]. "nop"
+ 			[16rE9] ->	[5]. "long unconditional jump"
+ 			[16rEB] ->	[2] "short unconditional jump" }!

Item was added:
+ ----- Method: CogX64Compiler>>jumpTargetPCAt: (in category 'disassembly') -----
+ jumpTargetPCAt: pc
+ 	<returnTypeC: #usqInt>
+ 	| size byte offset |
+ 	size := self instructionSizeAt: pc.
+ 	size = 2
+ 		ifTrue:
+ 			[byte := objectMemory byteAt: pc + 1.
+ 			 offset := (byte bitAnd: 16r80) = 0 ifTrue: [byte] ifFalse: [byte - 256]]
+ 		ifFalse:
+ 			[byte := objectMemory byteAt: pc + size - 1.
+ 			 offset := (byte bitAnd: 16r80) = 0 ifTrue: [byte] ifFalse: [byte - 256].
+ 			 offset := offset << 8 + (objectMemory byteAt: pc + size - 2).
+ 			 offset := offset << 8 + (objectMemory byteAt: pc + size - 3).
+ 			 offset := offset << 8 + (objectMemory byteAt: pc + size - 4)].
+ 	^pc + size + offset!

Item was added:
+ ----- Method: CogX64Compiler>>sizeHasModrm:at: (in category 'disassembly') -----
+ sizeHasModrm: op at: pc
+ 	| modrm mod ro rm |
+ 	modrm := objectMemory byteAt: pc + 1.
+ 	mod := modrm >> 6.
+ 	ro := modrm >> 3 bitAnd: 7.
+ 	rm := modrm bitAnd: 7.
+ 	mod = 3 ifTrue:
+ 		[^2].
+ 	rm ~= 4 ifTrue: "no SIB byte"
+ 		[^mod caseOf:
+ 		   {	[0]	->	[rm = 5
+ 						ifTrue: [6] "reg or 32-bit displacement"
+ 						ifFalse: [3]].
+ 			[1]	->	[3]. "8-bit displacement"
+ 			[2]	->	[6] }].
+ 	self halt: 'fall through in sizeHasModrm:at:'.
+ 	^0!

Item was added:
+ ----- Method: CogX64Compiler>>twoByteInstructionSizeAt: (in category 'disassembly') -----
+ twoByteInstructionSizeAt: pc
+ 	| op |
+ 	op := objectMemory byteAt: pc + 1. 
+ 	^(op bitAnd: 16rF0) caseOf:
+ 		{	[16r80]	->	[6 "long conditional jumps"] }!



More information about the Vm-dev mailing list