[Vm-dev] VM Maker: VMMaker.oscog-rmacnak.1560.mcz

commits at source.squeak.org commits at source.squeak.org
Sun Dec 6 23:01:31 UTC 2015


Ryan Macnak uploaded a new version of VMMaker to project VM Maker:
http://source.squeak.org/VMMaker/VMMaker.oscog-rmacnak.1560.mcz

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

Name: VMMaker.oscog-rmacnak.1560
Author: rmacnak
Time: 6 December 2015, 3:00:08.74 pm
UUID: 7fceca4c-cedf-42fb-bc90-2f786223abbc
Ancestors: VMMaker.oscog-eem.1559

Fill unused portions of methods with the stop instruction, not nop.

Explicitly initialize the code zone with stops. Explicitly clear the reclaimed portion of the method zone after a compaction.

Include the reclaimed portion of the method zone in the I-cache flush after a compaction: no point in leaving it in cache since it isn't a valid call/jump target.

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

Item was changed:
  ----- Method: CogARMCompiler>>concretizeStop (in category 'generate machine code - concretize') -----
  concretizeStop
- "generate a BKPT instruction. We could, given a good enough creative impulse and an over-active sense of humour, add some numerically encoded witticism to this instruction in bits 8-19 & 0-3. It has no effect on the execution but can be a way to specify which breakpoint has been hit etc."
  	<inline: true>
+ 	self machineCodeAt: 0 put: self stop.
- 	self machineCodeAt: 0 put: (AL <<28 bitOr: (16r42 <<20 bitOr:(7<<4))).
  	^machineCodeSize := 4!

Item was removed:
- ----- Method: CogARMCompiler>>nopsFrom:to: (in category 'generate machine code - support') -----
- nopsFrom: startAddr to: endAddr
- "fill with MOV R0, R0 no-op instructions"
- 	self assert: endAddr - startAddr + 1 \\ 4 = 0.
- 	startAddr to: endAddr by: 4 do:
- 		[:p| objectMemory 
- 			byteAt: p put: 16r0;
- 			byteAt: p+1 put: 16r0;
- 			byteAt: p+2 put: 16rA0;
- 			byteAt: p+3 put: 16rE1]!

Item was removed:
- ----- Method: CogARMCompiler>>padIfPossibleWithNopsFrom:to: (in category 'generate machine code') -----
- padIfPossibleWithNopsFrom: startAddr to: endAddr
- 	| nullBytes |
- 	nullBytes := (endAddr - startAddr + 1) \\ 4.
- 	self nopsFrom: startAddr to: endAddr - nullBytes.
- 	endAddr - nullBytes + 1 to: endAddr 
- 		do: [ :p | objectMemory byteAt: p put: 16r0]!

Item was added:
+ ----- Method: CogARMCompiler>>padIfPossibleWithStopsFrom:to: (in category 'generate machine code') -----
+ padIfPossibleWithStopsFrom: startAddr to: endAddr
+ 	| nullBytes |
+ 	nullBytes := (endAddr - startAddr + 1) \\ 4.
+ 	self stopsFrom: startAddr to: endAddr - nullBytes.
+ 	endAddr - nullBytes + 1 to: endAddr 
+ 		do: [ :p | objectMemory byteAt: p put: 16rFF]!

Item was added:
+ ----- Method: CogARMCompiler>>stop (in category 'encoding') -----
+ stop
+ "generate a BKPT instruction. We could, given a good enough creative impulse and an over-active sense of humour, add some numerically encoded witticism to this instruction in bits 8-19 & 0-3. It has no effect on the execution but can be a way to specify which breakpoint has been hit etc."
+ 	<inline: true>
+ 	^AL << 28 bitOr: (16r42 << 20 bitOr: (7 << 4))!

Item was added:
+ ----- Method: CogARMCompiler>>stopsFrom:to: (in category 'generate machine code - support') -----
+ stopsFrom: startAddr to: endAddr
+ 	self assert: endAddr - startAddr + 1 \\ 4 = 0.
+ 	startAddr to: endAddr by: 4 do: 
+ 		[:addr | objectMemory longAt: addr put: self stop].!

Item was removed:
- ----- Method: CogIA32Compiler>>nopsFrom:to: (in category 'generate machine code') -----
- nopsFrom: startAddr to: endAddr
- 	startAddr to: endAddr do:
- 		[:p| objectMemory byteAt: p put: 16r90]!

Item was removed:
- ----- Method: CogIA32Compiler>>padIfPossibleWithNopsFrom:to: (in category 'generate machine code') -----
- padIfPossibleWithNopsFrom: startAddr to: endAddr
- 	self nopsFrom: startAddr to: endAddr!

Item was added:
+ ----- Method: CogIA32Compiler>>padIfPossibleWithStopsFrom:to: (in category 'generate machine code') -----
+ padIfPossibleWithStopsFrom: startAddr to: endAddr
+ 	self stopsFrom: startAddr to: endAddr!

Item was added:
+ ----- Method: CogIA32Compiler>>stop (in category 'encoding') -----
+ stop
+ 	"int3"
+ 	<inline: true>
+ 	^16rCC!

Item was added:
+ ----- Method: CogIA32Compiler>>stopsFrom:to: (in category 'generate machine code') -----
+ stopsFrom: startAddr to: endAddr
+ 	startAddr to: endAddr do:
+ 		[:addr | objectMemory byteAt: addr put: self stop]!

Item was removed:
- ----- Method: CogMIPSELCompiler>>nopsFrom:to: (in category 'generate machine code') -----
- nopsFrom: startAddr to: endAddr
- 	self assert: endAddr - startAddr + 1 \\ 4 = 0.
- 	self assert: (self nop = 0).
- 	startAddr to: endAddr do: [:p| objectMemory byteAt: p put: 0].!

Item was removed:
- ----- Method: CogMIPSELCompiler>>padIfPossibleWithNopsFrom:to: (in category 'generate machine code') -----
- padIfPossibleWithNopsFrom: startAddr to: endAddr
- 	self flag: #bogus. "Methods should be initialized with the stop instruction, not nop."
- 
- 	startAddr to: endAddr - 1 by: 4 do: 
- 		[:addr | objectMemory longAt: addr put: self stop].!

Item was added:
+ ----- Method: CogMIPSELCompiler>>padIfPossibleWithStopsFrom:to: (in category 'generate machine code') -----
+ padIfPossibleWithStopsFrom: startAddr to: endAddr
+ 	startAddr to: endAddr - 1 by: 4 do: 
+ 		[:addr | objectMemory longAt: addr put: self stop].!

Item was added:
+ ----- Method: CogMIPSELCompiler>>stopsFrom:to: (in category 'generate machine code') -----
+ stopsFrom: startAddr to: endAddr
+ 	self assert: endAddr - startAddr + 1 \\ 4 = 0.
+ 	startAddr to: endAddr by: 4 do: 
+ 		[:addr | objectMemory longAt: addr put: self stop].!

Item was removed:
- ----- Method: CogX64Compiler>>nopsFrom:to: (in category 'generate machine code') -----
- nopsFrom: startAddr to: endAddr
- 	startAddr to: endAddr do:
- 		[:p| objectMemory byteAt: p put: 16r90]!

Item was removed:
- ----- Method: CogX64Compiler>>padIfPossibleWithNopsFrom:to: (in category 'generate machine code') -----
- padIfPossibleWithNopsFrom: startAddr to: endAddr
- 	self nopsFrom: startAddr to: endAddr!

Item was added:
+ ----- Method: CogX64Compiler>>padIfPossibleWithStopsFrom:to: (in category 'generate machine code') -----
+ padIfPossibleWithStopsFrom: startAddr to: endAddr
+ 	self stopsFrom: startAddr to: endAddr!

Item was added:
+ ----- Method: CogX64Compiler>>stopsFrom:to: (in category 'generate machine code') -----
+ stopsFrom: startAddr to: endAddr
+ 	startAddr to: endAddr do:
+ 		[:addr | objectMemory byteAt: addr put: self stop]!

Item was changed:
  ----- Method: Cogit>>compactCogCompiledCode (in category 'jit - api') -----
  compactCogCompiledCode
  	<api>
  	self assert: self noCogMethodsMaximallyMarked.
  	coInterpreter markActiveMethodsAndReferents.
  	methodZone freeOlderMethodsForCompaction.
  	self freePICsWithFreedTargets.
  	methodZone planCompaction.
  	coInterpreter updateStackZoneReferencesToCompiledCodePreCompaction.
  	methodZone relocateMethodsPreCompaction.
  	methodZone compactCompiledCode.
  	self assert: self allMethodsHaveCorrectHeader.
  	self assert: methodZone kosherYoungReferrers.
+ 	backEnd stopsFrom: methodZone freeStart to: methodZone youngReferrers - 1.
  	processor
  		flushICacheFrom: methodZoneBase asUnsignedInteger
+ 		to: methodZone youngReferrers asUnsignedInteger!
- 		to: methodZone freeStart asUnsignedInteger!

Item was changed:
  ----- Method: Cogit>>genEnilopmartFor:and:and:forCall:called: (in category 'initialization') -----
  genEnilopmartFor: regArg1 and: regArg2 and: regArg3 forCall: forCall called: trampolineName
  	"An enilopmart (the reverse of a trampoline) is a piece of code that makes
  	 the system-call-like transition from the C runtime into generated machine
  	 code.  The desired arguments and entry-point are pushed on a stackPage's
  	 stack.  The enilopmart pops off the values to be loaded into registers and
  	 then executes a return instruction to pop off the entry-point and jump to it.
  
  						BEFORE				AFTER			(stacks grow down)
  						whatever			stackPointer ->	whatever
  						target address =>	reg1 = reg1val, etc
  						reg1val				pc = target address
  						reg2val
  		stackPointer ->	reg3val"
  
  	<var: #trampolineName type: #'char *'>
  	<returnTypeC: #'void (*genEnilopmartForandandforCallcalled(sqInt regArg1, sqInt regArg2, sqInt regArg3, sqInt forCall, char *trampolineName))(void)'>
  
  	| size endAddress enilopmart |
  	self zeroOpcodeIndex.
  	backEnd maybeEstablishVarBase. "Must happen first; value may be used in genLoadStackPointers"
  	backEnd genLoadStackPointers.
  	regArg3 ifNotNil: [self PopR: regArg3].
  	regArg2 ifNotNil: [self PopR: regArg2].
  	self PopR: regArg1.
  	self genEnilopmartReturn: forCall.
  	self computeMaximumSizes.
  	size := self generateInstructionsAt: methodZoneBase.
  	endAddress := self outputInstructionsAt: methodZoneBase.
  	self assert: methodZoneBase + size = endAddress.
  	enilopmart := methodZoneBase.
  	methodZoneBase := self alignUptoRoutineBoundary: endAddress.
+ 	backEnd stopsFrom: endAddress to: methodZoneBase - 1.
- 	backEnd nopsFrom: endAddress to: methodZoneBase - 1.
  	self recordGeneratedRunTime: trampolineName address: enilopmart.
  	^self cCoerceSimple: enilopmart to: #'void (*)(void)'!

Item was changed:
  ----- Method: Cogit>>generateCogMethod: (in category 'generate machine code') -----
  generateCogMethod: selector
  	"We handle jump sizing simply.  First we make a pass that asks each
  	 instruction to compute its maximum size.  Then we make a pass that
  	 sizes jumps based on the maxmimum sizes.  Then we make a pass
  	 that fixes up jumps.  When fixing up a jump the jump is not allowed to
  	 choose a smaller offset but must stick to the size set in the second pass."
  	<returnTypeC: #'CogMethod *'>
  	| codeSize headerSize mapSize totalSize startAddress result method |
  	<var: #method type: #'CogMethod *'>
  	headerSize := self sizeof: CogMethod.
  	methodLabel address: methodZone freeStart.
  	self computeMaximumSizes.
  	methodLabel concretizeAt: methodZone freeStart.
  	codeSize := self generateInstructionsAt: methodLabel address + headerSize.
  	mapSize := self generateMapAt: nil start: methodLabel address + cmNoCheckEntryOffset.
  	totalSize := methodZone roundUpLength: headerSize + codeSize + mapSize.
  	totalSize > MaxMethodSize ifTrue:
  		[^self cCoerceSimple: MethodTooBig to: #'CogMethod *'].
  	startAddress := methodZone allocate: totalSize.
  	startAddress = 0 ifTrue:
  		[^self cCoerceSimple: InsufficientCodeSpace to: #'CogMethod *'].
  	self assert: startAddress + cmEntryOffset = entry address.
  	self assert: startAddress + cmNoCheckEntryOffset = noCheckEntry address.
  	result := self outputInstructionsAt: startAddress + headerSize.
  	self assert: startAddress + headerSize + codeSize = result.
+ 	backEnd padIfPossibleWithStopsFrom: result to: startAddress + totalSize - mapSize.
- 	backEnd padIfPossibleWithNopsFrom: result to: startAddress + totalSize - mapSize.
  	self generateMapAt: startAddress + totalSize - 1 start: startAddress + cmNoCheckEntryOffset.
  	self fillInBlockHeadersAt: startAddress.
  	method := self fillInMethodHeader: (self cCoerceSimple: startAddress to: #'CogMethod *')
  					size: totalSize
  					selector: selector.
  	postCompileHook ifNotNil:
  		[self perform: postCompileHook with: method.
  		 postCompileHook := nil].
  	^method!

Item was changed:
  ----- Method: Cogit>>initializeCodeZoneFrom:upTo: (in category 'initialization') -----
  initializeCodeZoneFrom: startAddress upTo: endAddress
  	<api>
+ 	self initializeBackend.
+ 	backEnd stopsFrom: startAddress to: endAddress - 1.
  	self cCode: [self sqMakeMemoryExecutableFrom: startAddress To: endAddress]
  		inSmalltalk: [self initializeProcessor].
  	codeBase := methodZoneBase := startAddress.
  	minValidCallAddress := (codeBase min: coInterpreter interpretAddress)
  								min: coInterpreter primitiveFailAddress.
- 	self initializeBackend.
  	methodZone manageFrom: methodZoneBase to: endAddress.
  	self maybeGenerateCheckFeatures.
  	self maybeGenerateICacheFlush.
  	self generateVMOwnerLockFunctions.
  	ceGetSP := self cCoerceSimple: self genGetLeafCallStackPointer to: #'unsigned long (*)(void)'.
  	self generateStackPointerCapture.
  	self generateTrampolines.
  	self computeEntryOffsets.
  	self generateClosedPICPrototype.
  	methodZone manageFrom: methodZoneBase to: endAddress.
  	"N.B. this is assumed to be the last thing done in initialization; see Cogit>>initialized"
  	self generateOpenPICPrototype!

Item was changed:
  ----- Method: Cogit>>outputInstructionsForGeneratedRuntimeAt: (in category 'initialization') -----
  outputInstructionsForGeneratedRuntimeAt: startAddress
  	"Output instructions generated for one of the generated run-time routines, a trampoline, etc"
  	| size endAddress |
  	<inline: false>
  	self computeMaximumSizes.
  	methodLabel address: startAddress. "for addressIsInCurrentCompilation:"
  	size := self generateInstructionsAt: startAddress.
  	endAddress := self outputInstructionsAt: startAddress.
  	self assert: startAddress + size = endAddress.
  	methodZoneBase := self alignUptoRoutineBoundary: endAddress.
+ 	backEnd stopsFrom: endAddress to: methodZoneBase - 1.
- 	backEnd nopsFrom: endAddress to: methodZoneBase - 1.
  	self cCode: '' inSmalltalk: [methodZone freeStart: methodZoneBase].
  	^startAddress!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genCallPICEnilopmartNumArgs: (in category 'initialization') -----
  genCallPICEnilopmartNumArgs: numArgs
  	"Generate special versions of the ceCallCogCodePopReceiverAndClassRegs
  	 enilopmart that also pop register args from the stack to undo the pushing of
  	 register args in the abort/miss trampolines."
  	<returnTypeC: 'void (*genCallPICEnilopmartNumArgs(sqInt numArgs))(void)'>
  	| size endAddress enilopmart |
  	self zeroOpcodeIndex.
  	backEnd maybeEstablishVarBase. "Must happen first; value may be used in genLoadStackPointers"
  	backEnd genLoadStackPointers.
  	self PopR: ClassReg. "cacheTag"
  	self PopR: TempReg. "entry-point"
  	self PopR: (backEnd hasLinkRegister ifTrue: [LinkReg] ifFalse: [SendNumArgsReg]). "retpc"
  	numArgs > 0 ifTrue:
  		[numArgs > 1 ifTrue:
  			[self PopR: Arg1Reg.
  			 self assert: self numRegArgs = 2].
  		 self PopR: Arg0Reg].
  	self PopR: ReceiverResultReg.
  	backEnd hasLinkRegister ifFalse: [self PushR: SendNumArgsReg]. "retpc"
  	self JumpR: TempReg.
  	self computeMaximumSizes.
  	size := self generateInstructionsAt: methodZoneBase.
  	endAddress := self outputInstructionsAt: methodZoneBase.
  	self assert: methodZoneBase + size = endAddress.
  	enilopmart := methodZoneBase.
  	methodZoneBase := self alignUptoRoutineBoundary: endAddress.
+ 	backEnd stopsFrom: endAddress to: methodZoneBase - 1.
- 	backEnd nopsFrom: endAddress to: methodZoneBase - 1.
  	self recordGeneratedRunTime: (self trampolineName: 'ceCallPIC' numRegArgs: numArgs) address: enilopmart.
  	^self cCoerceSimple: enilopmart to: #'void (*)(void)'!



More information about the Vm-dev mailing list