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

commits at source.squeak.org commits at source.squeak.org
Thu Oct 8 02:04:33 UTC 2020


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

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

Name: VMMaker.oscog-eem.2836
Author: eem
Time: 7 October 2020, 7:04:24.98048 pm
UUID: 9203f225-3af0-4c06-b652-99c13e86694a
Ancestors: VMMaker.oscog-eem.2835

Cogoit: Fix an occasional initialization crash due to address space randomization. Don't enforce the range check in rewriteCallAt:target: et al until the Cogit is initializaed hence avoiding crashes during expectedClosedPICPrototype:'s validation.

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

Item was changed:
  ----- Method: CogARMCompiler>>rewriteTransferAt:target: (in category 'inline cacheing') -----
  rewriteTransferAt: callSiteReturnAddress target: callTargetAddress
  	"Rewrite a call/jump instruction to call a different target.  This variant is used to link PICs
  	 in ceSendMiss et al, and to rewrite call/jumps in CPICs.
  	Answer the extent of
  	 the code change which is used to compute the range of the icache to flush."
  	<var: #callSiteReturnAddress type: #usqInt>
  	<var: #callTargetAddress type: #usqInt>
  	| callDistance instr |
  	"for debug - [cogit disassembleFrom: callSiteReturnAddress - 10 to: callSiteReturnAddress - 1]."
+ 	(cogit initialized and: [callTargetAddress < cogit minCallAddress]) ifTrue:
+ 		[self error: 'linking callsite to invalid address'].
- 	false
- 		ifTrue: [self assert: callTargetAddress >= cogit minCallAddress]
- 		ifFalse: [callTargetAddress >= cogit minCallAddress ifFalse:
- 					[self error: 'linking callsite to invalid address']].
  
  	callDistance := (callTargetAddress - (callSiteReturnAddress + 8 "pc offset"- 4 "return offset")) signedIntToLong.
  	self assert: (self isInImmediateJumpRange: callDistance). "we don't support long call updates, yet"
  
  	instr := self instructionBeforeAddress: callSiteReturnAddress.
  	self assert: ((self instructionIsB: instr) or: [self instructionIsBL: instr]).
  	
  	objectMemory longAt:  (self instructionAddressBefore: callSiteReturnAddress) put: ((instr bitAnd: 16rFF000000) bitOr: (callDistance // 4 bitAnd: 16rFFFFFF)).
  
  	self assert: (self callTargetFromReturnAddress: callSiteReturnAddress) = callTargetAddress.
  
  	^4!

Item was changed:
  ----- Method: CogIA32Compiler>>rewriteCallAt:target: (in category 'inline cacheing') -----
  rewriteCallAt: callSiteReturnAddress target: callTargetAddress
  	"Rewrite a call instruction to call a different target.  This variant is used to link PICs
  	 in ceSendMiss et al, and to rewrite cached primitive calls.   Answer the extent of
  	 the code change which is used to compute the range of the icache to flush."
  	<var: #callSiteReturnAddress type: #usqInt>
  	<var: #callTargetAddress type: #usqInt>
  	| callDistance |
  	"self cCode: ''
  		inSmalltalk: [cogit disassembleFrom: callSiteReturnAddress - 10 to: callSiteReturnAddress - 1]."
+ 	(cogit initialized and: [callTargetAddress < cogit minCallAddress]) ifTrue:
+ 		[self error: 'linking callsite to invalid address'].
- 	false
- 		ifTrue: [self assert: callTargetAddress >= cogit minCallAddress]
- 		ifFalse: [callTargetAddress >= cogit minCallAddress ifFalse:
- 					[self error: 'linking callsite to invalid address']].
  	callDistance := (callTargetAddress - callSiteReturnAddress) signedIntToLong.
  	objectMemory
  		byteAt: callSiteReturnAddress - 1 put: (callDistance >> 24 bitAnd: 16rFF);
  		byteAt: callSiteReturnAddress - 2 put: (callDistance >> 16 bitAnd: 16rFF);
  		byteAt: callSiteReturnAddress - 3 put: (callDistance >>   8 bitAnd: 16rFF);
  		byteAt: callSiteReturnAddress - 4 put: (callDistance            bitAnd: 16rFF).
  	self assert: (self callTargetFromReturnAddress: callSiteReturnAddress) = callTargetAddress.
  	"self cCode: ''
  		inSmalltalk: [cogit disassembleFrom: callSiteReturnAddress - 10 to: callSiteReturnAddress - 1]."
  	^5!

Item was changed:
  ----- Method: CogIA32Compiler>>rewriteInlineCacheAt:tag:target: (in category 'inline cacheing') -----
  rewriteInlineCacheAt: callSiteReturnAddress tag: cacheTag target: callTargetAddress
  	"Rewrite an inline cache to call a different target for a new tag.  This variant is used
  	 to link unlinked sends in ceSend:to:numArgs: et al.  Answer the extent of the code
  	 change which is used to compute the range of the icache to flush."
  	<var: #callSiteReturnAddress type: #usqInt>
  	<var: #callTargetAddress type: #usqInt>
  	| callDistance |
  	"self cCode: ''
  		inSmalltalk: [cogit disassembleFrom: callSiteReturnAddress - 10 to: callSiteReturnAddress - 1]."
+ 	(cogit initialized and: [callTargetAddress < cogit minCallAddress]) ifTrue:
+ 		[self error: 'linking callsite to invalid address'].
- 	false
- 		ifTrue: [self assert: callTargetAddress >= cogit minCallAddress]
- 		ifFalse: [callTargetAddress >= cogit minCallAddress ifFalse:
- 					[self error: 'linking callsite to invalid address']].
  	callDistance := (callTargetAddress - callSiteReturnAddress) signedIntToLong.
  	objectMemory
  		byteAt: callSiteReturnAddress - 1 put: (callDistance >> 24 bitAnd: 16rFF);
  		byteAt: callSiteReturnAddress - 2 put: (callDistance >> 16 bitAnd: 16rFF);
  		byteAt: callSiteReturnAddress - 3 put: (callDistance >>   8 bitAnd: 16rFF);
  		byteAt: callSiteReturnAddress - 4 put: (callDistance            bitAnd: 16rFF);
  		byteAt: callSiteReturnAddress - 6 put: (cacheTag >> 24 bitAnd: 16rFF);
  		byteAt: callSiteReturnAddress - 7 put: (cacheTag >> 16 bitAnd: 16rFF);
  		byteAt: callSiteReturnAddress - 8 put: (cacheTag >>   8 bitAnd: 16rFF);
  		byteAt: callSiteReturnAddress - 9 put: (cacheTag            bitAnd: 16rFF).
  	self assert: (self callTargetFromReturnAddress: callSiteReturnAddress) = callTargetAddress.
  	"self cCode: ''
  		inSmalltalk: [cogit disassembleFrom: callSiteReturnAddress - 10 to: callSiteReturnAddress - 1]."
  	^10!

Item was changed:
  ----- Method: CogInLineLiteralsARMCompiler>>rewriteInlineCacheAt:tag:target: (in category 'inline cacheing') -----
  rewriteInlineCacheAt: callSiteReturnAddress tag: cacheTag target: callTargetAddress
  	"Rewrite an inline cache to call a different target for a new tag.  This variant is used
  	 to link unlinked sends in ceSend:to:numArgs: et al.  Answer the extent of the code
  	 change which is used to compute the range of the icache to flush."
  	<var: #callSiteReturnAddress type: #usqInt>
  	<var: #callTargetAddress type: #usqInt>
  	| call callDistance |
+ 	(cogit initialized and: [callTargetAddress < cogit minCallAddress]) ifTrue:
+ 		[self error: 'linking callsite to invalid address'].
- 	false
- 		ifTrue: [self assert: callTargetAddress >= cogit minCallAddress]
- 		ifFalse: [callTargetAddress >= cogit minCallAddress ifFalse:
- 					[self error: 'linking callsite to invalid address']].
  	callDistance := (callTargetAddress - (callSiteReturnAddress + 8 "pc offset"- 4 "return offset")) signedIntToLong.
  	self assert: (self isInImmediateJumpRange: callDistance). "we don't support long call updates here"
  	call := self bl: callDistance.
  	objectMemory longAt: (self instructionAddressBefore: callSiteReturnAddress ) put: call.
  	self insert32BitOperand: cacheTag into4InstructionsPreceding: (self instructionAddressBefore: callSiteReturnAddress ).
  	self assert: (self callTargetFromReturnAddress: callSiteReturnAddress) = callTargetAddress.
  	self assert: (self extract32BitOperandFrom4InstructionsPreceding: (self instructionAddressBefore: callSiteReturnAddress )) = cacheTag.
  	"self cCode: ''
  		inSmalltalk: [cogit disassembleFrom: callSiteReturnAddress - 20 to: callSiteReturnAddress - 1]."
  	^20!

Item was changed:
  ----- Method: CogOutOfLineLiteralsARMCompiler>>rewriteInlineCacheAt:tag:target: (in category 'inline cacheing') -----
  rewriteInlineCacheAt: callSiteReturnAddress tag: cacheTag target: callTargetAddress
  	"Rewrite an inline cache to call a different target for a new tag.  This variant is used
  	 to link unlinked sends in ceSend:to:numArgs: et al.  Answer the extent of the code
  	 change which is used to compute the range of the icache to flush."
  	<var: #callSiteReturnAddress type: #usqInt>
  	<var: #callTargetAddress type: #usqInt>
  	| call callDistance |
+ 	(cogit initialized and: [callTargetAddress < cogit minCallAddress]) ifTrue:
- 	callTargetAddress >= cogit minCallAddress ifFalse:
  		[self error: 'linking callsite to invalid address'].
  	callDistance := (callTargetAddress - (callSiteReturnAddress + 8 "pc offset"- 4 "return offset")) signedIntToLong.
  	self assert: (self isInImmediateJumpRange: callDistance). "we don't support long call updates here"
  	call := self bl: callDistance.
  	objectMemory
  		longAt: (self instructionAddressBefore: callSiteReturnAddress ) put: call;
  		longAt: (self pcRelativeAddressAt: callSiteReturnAddress - 8) put: cacheTag.
  	self assert: (self inlineCacheTagAt: callSiteReturnAddress) = cacheTag.
  	"self cCode: ''
  		inSmalltalk: [cogit disassembleFrom: callSiteReturnAddress - 8 to: (self pcRelativeAddressAt: callSiteReturnAddress - 8)]."
  	^4!

Item was changed:
  ----- Method: CogX64Compiler>>rewriteCallAt:target: (in category 'inline cacheing') -----
  rewriteCallAt: callSiteReturnAddress target: callTargetAddress
  	"Rewrite a call instruction to call a different target.  This variant is used to link PICs
  	 in ceSendMiss et al, and to rewrite cached primitive calls.   Answer the extent of
  	 the code change which is used to compute the range of the icache to flush."
  	<var: #callSiteReturnAddress type: #usqInt>
  	<var: #callTargetAddress type: #usqInt>
  	| callDistance |
  	"self cCode: ''
  		inSmalltalk: [cogit disassembleFrom: callSiteReturnAddress - 10 to: callSiteReturnAddress - 1]."
+ 	(cogit initialized and: [callTargetAddress < cogit minCallAddress]) ifTrue:
+ 		[self error: 'linking callsite to invalid address'].
- 	false
- 		ifTrue: [self assert: callTargetAddress >= cogit minCallAddress]
- 		ifFalse: [callTargetAddress >= cogit minCallAddress ifFalse:
- 					[self error: 'linking callsite to invalid address']].
  	callDistance := (callTargetAddress - callSiteReturnAddress) signedIntToLong.
  	objectMemory
  		byteAt: callSiteReturnAddress - 1 put: (callDistance >> 24 bitAnd: 16rFF);
  		byteAt: callSiteReturnAddress - 2 put: (callDistance >> 16 bitAnd: 16rFF);
  		byteAt: callSiteReturnAddress - 3 put: (callDistance >>   8 bitAnd: 16rFF);
  		byteAt: callSiteReturnAddress - 4 put: (callDistance            bitAnd: 16rFF).
  	self assert: (self callTargetFromReturnAddress: callSiteReturnAddress) = callTargetAddress.
  	"self cCode: ''
  		inSmalltalk: [cogit disassembleFrom: callSiteReturnAddress - 10 to: callSiteReturnAddress - 1]."
  	^5!

Item was changed:
  ----- Method: CogX64Compiler>>rewriteInlineCacheAt:tag:target: (in category 'inline cacheing') -----
  rewriteInlineCacheAt: callSiteReturnAddress tag: cacheTag target: callTargetAddress
  	"Rewrite an inline cache to call a different target for a new tag.  This variant is used
  	 to link unlinked sends in ceSend:to:numArgs: et al.  Answer the extent of the code
  	 change which is used to compute the range of the icache to flush.
  	 N.B.  On 64-bit platforms the inline cache tag is only 32-bits wide, hence this code
  	 is identical to that for the IA32."
  	<var: #callSiteReturnAddress type: #usqInt>
  	<var: #callTargetAddress type: #usqInt>
  	| callDistance |
  	"self cCode: ''
  		inSmalltalk: [cogit disassembleFrom: callSiteReturnAddress - 12 to: callSiteReturnAddress - 1]."
+ 	(cogit initialized and: [callTargetAddress < cogit minCallAddress]) ifTrue:
+ 		[self error: 'linking callsite to invalid address'].
- 	false
- 		ifTrue: [self assert: callTargetAddress >= cogit minCallAddress]
- 		ifFalse: [callTargetAddress >= cogit minCallAddress ifFalse:
- 					[self error: 'linking callsite to invalid address']].
  	callDistance := (callTargetAddress - callSiteReturnAddress) signedIntToLong.
  	objectMemory
  		byteAt: callSiteReturnAddress - 1 put: (callDistance >> 24 bitAnd: 16rFF);
  		byteAt: callSiteReturnAddress - 2 put: (callDistance >> 16 bitAnd: 16rFF);
  		byteAt: callSiteReturnAddress - 3 put: (callDistance >>   8 bitAnd: 16rFF);
  		byteAt: callSiteReturnAddress - 4 put: (callDistance            bitAnd: 16rFF);
  		byteAt: callSiteReturnAddress - 6 put: (cacheTag >> 24 bitAnd: 16rFF);
  		byteAt: callSiteReturnAddress - 7 put: (cacheTag >> 16 bitAnd: 16rFF);
  		byteAt: callSiteReturnAddress - 8 put: (cacheTag >>   8 bitAnd: 16rFF);
  		byteAt: callSiteReturnAddress - 9 put: (cacheTag            bitAnd: 16rFF).
  	self assert: (self callTargetFromReturnAddress: callSiteReturnAddress) = callTargetAddress.
  	"self cCode: ''
  		inSmalltalk: [cogit disassembleFrom: callSiteReturnAddress - 12 to: callSiteReturnAddress - 1]."
  	^12!

Item was changed:
  ----- Method: Cogit>>initialized (in category 'testing') -----
  initialized
+ 	"Answerr if the code generator has been initialized (all trampolines and prtotypes
+ 	 have been generated and the code generator is ready to start compiling methods.
+ 	 Since the last thing is the generation of the open PIC prototype, its size is the marker."
+ 	<inline: #always>
+ 	^self cCode: [openPICSize] inSmalltalk: [openPICSize isInteger]!
- 	<doNotGenerate>
- 	^openPICSize isInteger!

Item was changed:
  ----- Method: InterpreterPrimitives>>primitiveSetDisplayMode (in category 'I/O primitives') -----
  primitiveSetDisplayMode
+ 	"Ask the GUI to set the requested display mode.
- 	"Ask trhe GUI to set the requested display mode.
  	 See DisplayScreen class depth:width:height:fullscreen:"
  	| fsFlag h w d okay |
  	fsFlag := self booleanValueOf: self stackTop.
  	h := self stackIntegerValue: 1.
  	w := self stackIntegerValue: 2.
  	d := self stackIntegerValue: 3.
  	self successful ifFalse:
  		[^self primitiveFailFor: PrimErrBadArgument].
  	okay := self ioSetDisplayMode: w _: h _: d _: fsFlag.
  	self successful ifFalse:
  		[^self primitiveFailFor: PrimErrOperationFailed].
  	self methodReturnBool: okay!

Item was changed:
  ----- Method: VMClass class>>openCogitMultiWindowBrowser (in category 'utilities') -----
  openCogitMultiWindowBrowser
  	"Answer a new multi-window browser on the ObjectMemory classes, the Cog Interpreter classes, and the main JIT classes"
  	"self openCogitMultiWindowBrowser"
  	| b |
  	b := Browser open.
+ 	{CogRTLOpcodes. CogAbstractRegisters. CogAbstractInstruction },
- 	{CogRTLOpcodes. CogAbstractRegisters },
  	self sortedAbstractInstructionClasses,
  	Cogit withAllSubclasses,
  	{CogMethodZone },
  	CogObjectRepresentation withAllSubclasses,
  	CogBytecodeFixup withAllSubclasses,
  	CogSimStackEntry withAllSubclasses,
  	{VMStructType. VMMaker. CCodeGenerator. TMethod}
  		do: [:class|
  			b selectCategoryForClass: class; selectClass: class]
  		separatedBy:
  			[b multiWindowState addNewWindow].
  	b multiWindowState selectWindowIndex: 1!



More information about the Vm-dev mailing list