[Vm-dev] VM Maker: VMMaker.oscog-tpr.1340.mcz

commits at source.squeak.org commits at source.squeak.org
Sat Jun 6 21:48:25 UTC 2015


tim Rowledge uploaded a new version of VMMaker to project VM Maker:
http://source.squeak.org/VMMaker/VMMaker.oscog-tpr.1340.mcz

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

Name: VMMaker.oscog-tpr.1340
Author: tpr
Time: 6 June 2015, 2:46:53.877 pm
UUID: 4826ecce-62d5-4976-ae28-aeb9abeb88a5
Ancestors: VMMaker.oscog-eem.1339

Make all the usages of flushICacheFrom:to: work with start-address to byte-after-end-address. Irrelevant to x86, perfect for ARM, matches most of the usage already in place.

Fix up a few type complaints from gcc. Whiny, whiny.

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

Item was changed:
  ----- Method: CogARMCompiler>>flushICacheFrom:to: (in category 'inline cacheing') -----
  flushICacheFrom: startAddress "<Integer>" to: endAddress "<Integer>"
+ 	<cmacro: '(me,startAddress,endAddress) __clear_cache((char*) startAddress, (char*) (endAddress ))'>
+ 	"On ARM we almost certainly need to flush and wash hands. On linux we use __clear_cache (see http://community.arm.com/groups/processors/blog/2010/02/17/caches-and-self-modifying-code for a decent example) and remember that the end address is *exclusive* so we can just use the end address passed in since it is always the byte after the actual last one needing flushing"
- 	<cmacro: '(me,startAddress,endAddress) __clear_cache((char*) startAddress, (char*) (endAddress + 4))'>
- 	"On ARM we almost certainly need to flush and wash hands. On linux we use __clear_cache (see http://community.arm.com/groups/processors/blog/2010/02/17/caches-and-self-modifying-code for a decent example) and remember that the end address is *exclusive* so we add 4 for now"
  	self halt: #ceFlushICache!

Item was changed:
  ----- Method: CogMethodZone>>relocateMethodsPreCompaction (in category 'compaction') -----
  relocateMethodsPreCompaction
  	"All surviving methods have had the amount they are going to relocate by
  	 stored in their objectHeader fields.  Relocate all relative calls so that after
  	 the compaction of both the method containing each call and the call target
  	 the calls invoke the same target."
  	| cogMethod |
  	<var: #cogMethod type: #'CogMethod *'>
  	cogMethod := cogit cCoerceSimple: baseAddress to: #'CogMethod *'.
+ 	[cogMethod < (cogit cCoerceSimple: mzFreeStart to: #'CogMethod *')] whileTrue:
- 	[cogMethod < mzFreeStart] whileTrue:
  		[cogMethod cmType ~= CMFree ifTrue:
  			[cogMethod cmType = CMClosedPIC
  				ifTrue: [cogit relocateCallsInClosedPIC: cogMethod]
  				ifFalse: [cogit relocateCallsAndSelfReferencesInMethod: cogMethod]].
  		 cogMethod := self methodAfter: cogMethod].
  	self relocateAndPruneYoungReferrers.
  	^true!

Item was changed:
  ----- Method: CogObjectRepresentationForSpur>>genStoreCheckContextReceiverTrampoline (in category 'initialization') -----
  genStoreCheckContextReceiverTrampoline
- 	<var: #aString type: #'char *'>
  	"Create a trampoline to store-check the update of the receiver in a closure's
  	 outerContext in compileBlockFrameBuild:."
  	| startAddress |
  	startAddress := cogit methodZoneBase.
  	cogit zeroOpcodeIndex.
  	self genStoreCheckReceiverReg: ReceiverResultReg valueReg: Arg0Reg scratchReg: TempReg inFrame: false.
  	cogit RetN: 0.
  	cogit outputInstructionsForGeneratedRuntimeAt: startAddress.
  	cogit recordGeneratedRunTime: 'ceStoreCheckContextReceiver' address: startAddress.
  	cogit recordRunTimeObjectReferences.
  	^startAddress!

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 *'>
  	<var: #callerMethod 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 asUnsignedInteger.
  	targetMethod := self cCoerceSimple: innerReturn - missOffset to: #'CogMethod *'.
  	(objectMemory isOopForwarded: receiver) ifTrue:
  		[^coInterpreter ceSendFromInLineCacheMiss: targetMethod].
  	outerReturn := coInterpreter stackTop asUnsignedInteger.
  	self assert: (outerReturn between: methodZoneBase and: methodZone freeStart).
  	entryPoint := backEnd callTargetFromReturnAddress: outerReturn.
  
  	self assert: targetMethod selector ~= objectMemory nilObject.
  	self cppIf: NewspeakVM ifTrue:
  		[| callerMethod annotation |
  		 self assert: targetMethod asInteger + cmEntryOffset = entryPoint.
  		 callerMethod := coInterpreter mframeHomeMethod: coInterpreter getFramePointer.
  		 self assert: (outerReturn
  						between: callerMethod asUnsignedInteger + cmNoCheckEntryOffset
  						and: callerMethod asUnsignedInteger + callerMethod blockSize).
  		 annotation := self annotationForMcpc: outerReturn in: callerMethod.
  		 self assert: annotation >= IsSendCall.
  		 "Avoid the effort of implementing PICs for the relatively high dynamic frequency
  		  self send and simply rebind the send site (for now)."
  		 annotation = IsNSSelfSend ifTrue:
  			[^coInterpreter
  				ceSelfSend: targetMethod selector
  				to: receiver
  				numArgs: targetMethod cmNumArgs].
  		 "Avoid the effort of implementing PICs for the relatively low dynamic frequency
  		  dynamic super send and simply rebind the send site."
  		 annotation = IsNSDynamicSuperSend 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: [(backEnd inlineCacheTagAt: outerReturn) = self picAbortDiscriminatorValue
  	 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:
  			["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 asUnsignedInteger to: pic asUnsignedInteger + closedPICSize].
  	"Relink the send site to the pic.  If to an open PIC then reset the cache tag to the selector,
  	 for the benefit of the cacheTag assert check in checkIfValidObjectRef:pc:cogMethod:."
  	extent := pic cmType = CMOpenPIC
  				ifTrue:
  					[backEnd
  						rewriteInlineCacheAt: outerReturn
  						tag: targetMethod selector
  						target: pic asInteger + cmEntryOffset]
  				ifFalse:
  					[backEnd
  						rewriteCallAt: outerReturn
  						target: pic asInteger + cmEntryOffset].
+ 	processor flushICacheFrom: outerReturn asUnsignedInteger - extent to: outerReturn asUnsignedInteger.
- 	processor flushICacheFrom: outerReturn asUnsignedInteger - 1 - extent to: outerReturn asUnsignedInteger - 1.
  	"Jump back into the pic at its entry in case this is an MNU (newTargetMethodOrNil is nil)"
  	coInterpreter
  		executeCogPIC: pic
  		fromLinkedSendWithReceiver: receiver
  		andCacheTag: (backEnd inlineCacheTagAt: outerReturn).
  	"NOTREACHED"
  	^nil!

Item was changed:
  ----- Method: Cogit>>linkSendAt:in:to:offset:receiver: (in category 'in-line cacheing') -----
  linkSendAt: callSiteReturnAddress in: sendingMethod to: targetMethod offset: theEntryOffset receiver: receiver
  	<api>
  	<var: #sendingMethod type: #'CogMethod *'>
  	<var: #targetMethod type: #'CogMethod *'>
  	| inlineCacheTag address extent |
  	self assert: (theEntryOffset = cmEntryOffset or: [theEntryOffset = cmNoCheckEntryOffset]).
  	self assert: (callSiteReturnAddress between: methodZoneBase and: methodZone freeStart).
  	inlineCacheTag := theEntryOffset = cmNoCheckEntryOffset
  						ifTrue: [targetMethod selector "i.e. no change"]
  						ifFalse: [objectRepresentation inlineCacheTagForInstance: receiver].
  	(objectRepresentation inlineCacheTagIsYoung: inlineCacheTag) ifTrue:
  		[methodZone ensureInYoungReferrers: sendingMethod].
  	address := targetMethod asInteger + theEntryOffset.
  	extent := backEnd
  				rewriteInlineCacheAt: callSiteReturnAddress
  				tag: inlineCacheTag
  				target: address.
  	processor
+ 		flushICacheFrom: callSiteReturnAddress asUnsignedInteger  - extent
+ 		to: callSiteReturnAddress asUnsignedInteger !
- 		flushICacheFrom: callSiteReturnAddress asUnsignedInteger - 1 - extent
- 		to: callSiteReturnAddress asUnsignedInteger - 1!

Item was changed:
  ----- Method: Cogit>>markLiteralsAndUnlinkIfUnmarkedSend:pc:method: (in category 'garbage collection') -----
  markLiteralsAndUnlinkIfUnmarkedSend: annotation pc: mcpc method: cogMethod
  	"Mark and trace literals.  Unlink sends that have unmarked cache tags or targets."
  	<var: #mcpc type: #'char *'>
  	<var: #nsSendCache type: #'NSSendCache *'>
  	| literal |
  	annotation = IsObjectReference ifTrue:
  		[literal := backEnd literalBeforeFollowingAddress: mcpc asUnsignedInteger.
  		 (objectRepresentation
  				markAndTraceLiteral: literal
  				in: (self cCoerceSimple: cogMethod to: #'CogMethod *')
  				atpc: mcpc asUnsignedInteger) ifTrue:
  			[codeModified := true]].
  
  	self cppIf: NewspeakVM ifTrue:
  		[annotation = IsNSSendCall ifTrue:
  			[| nsSendCache entryPoint targetMethod sel eo |
  			nsSendCache := self nsSendCacheFromReturnAddress: mcpc asInteger.
  			entryPoint := nsSendCache target.
  			entryPoint ~= 0 ifTrue: "Send is linked"
  				[targetMethod := entryPoint - cmNoCheckEntryOffset.
  				 (self markAndTraceOrFreeCogMethod: targetMethod
  					firstVisit: targetMethod asUnsignedInteger > mcpc asUnsignedInteger) ifTrue:	
  						[self voidNSSendCache: nsSendCache]].
  			sel := nsSendCache selector.
  			(objectMemory isForwarded: sel)
  				ifFalse: [objectMemory markAndTrace: sel]
  				ifTrue: [sel := objectMemory followForwarded: literal.
  						nsSendCache selector: sel.
  						self markAndTraceUpdatedLiteral: sel in: (self cCoerceSimple: cogMethod to: #'CogMethod *')].
  			eo := nsSendCache enclosingObject.
  			eo ~= 0 ifTrue:
  				[(objectMemory isForwarded: eo)
  					ifFalse: [objectMemory markAndTrace: eo]
  					ifTrue: [eo := objectMemory followForwarded: literal.
  							nsSendCache enclosingObject: eo.
  							self markAndTraceUpdatedLiteral: eo in: (self cCoerceSimple: cogMethod to: #'CogMethod *')]]]].
  
  	(self isPureSendAnnotation: annotation) ifTrue:
  		[self offsetCacheTagAndCouldBeObjectAt: mcpc annotation: annotation into:
  			[:entryPoint :cacheTag :tagCouldBeObj | | cacheTagMarked |
  			 cacheTagMarked := tagCouldBeObj and: [objectRepresentation cacheTagIsMarked: cacheTag].
  			 entryPoint > methodZoneBase
  				ifTrue: "It's a linked send."
  					[self targetMethodAndSendTableFor: entryPoint annotation: annotation into:
  						[:targetMethod :sendTable| 
  						 (cacheTagMarked not
  						  or: [self markAndTraceOrFreeCogMethod: targetMethod
  								firstVisit: targetMethod asUnsignedInteger > mcpc asUnsignedInteger]) ifTrue:
  							["Either the cacheTag is unmarked (e.g. new class) or the target
  							  has been freed (because it is unmarked), so unlink the send."
  							 self unlinkSendAt: mcpc targetMethod: targetMethod sendTable: sendTable.
  							 objectRepresentation
  								markAndTraceLiteral: targetMethod selector
  								in: targetMethod
  								at: (self addressOf: targetMethod selector put: [:val| targetMethod selector: val])]]]
  				ifFalse:  "cacheTag is selector"
  					[(objectRepresentation
  							markAndTraceCacheTagLiteral: cacheTag
+ 							in: (self cCoerceSimple: cogMethod to: #'CogMethod *')
- 							in: cogMethod
  							atpc: mcpc asUnsignedInteger) ifTrue:
  						[codeModified := true]]]].
  
  	^0 "keep scanning"!

Item was changed:
  ----- Method: Cogit>>patchToOpenPICFor:numArgs:receiver: (in category 'in-line cacheing') -----
  patchToOpenPICFor: selector numArgs: numArgs receiver: receiver
  	"Code entry closed PIC full or miss to an instance of a young class or to a young target method.
  	 Attempt to patch the send site to an open PIC.  Answer if the attempt succeeded; in fact it will
  	 only return if the attempt failed.
  	 The stack looks like:
  			receiver
  			args
  	 sp=>	sender return address"
  	<api>
  	| oPIC outerReturn extent |
  	<var: #oPIC type: #'CogMethod *'>
  	outerReturn := coInterpreter stackTop.
  	"See if an Open PIC is already available."
  	oPIC := methodZone openPICWithSelector: selector.
  	oPIC isNil ifTrue:
  		["otherwise attempt to create an Open PIC."
  		oPIC := self cogOpenPICSelector: selector numArgs: numArgs.
  		(oPIC asInteger between: MaxNegativeErrorCode and: -1) ifTrue:
  			["For some reason the PIC couldn't be generated, most likely a lack of code memory."
  			oPIC asInteger = InsufficientCodeSpace ifTrue:
  				[coInterpreter callForCogCompiledCodeCompaction].
  			^false]].
  	extent := backEnd
  				rewriteInlineCacheAt: outerReturn
  				tag: selector
  				target: oPIC asInteger + cmEntryOffset.
  	processor
+ 		flushICacheFrom: outerReturn asUnsignedInteger - extent to: outerReturn asUnsignedInteger;
- 		flushICacheFrom: outerReturn asUnsignedInteger - 1 - extent to: outerReturn asUnsignedInteger - 1;
  		flushICacheFrom: oPIC asUnsignedInteger to: oPIC asUnsignedInteger + openPICSize.
  	"Jump into the oPIC at its entry"
  	coInterpreter executeCogMethod: oPIC fromLinkedSendWithReceiver: receiver.
  	"NOTREACHED"
  	^true!

Item was changed:
  ----- Method: Cogit>>trampolineName:numArgs: (in category 'initialization') -----
  trampolineName: routinePrefix numArgs: numArgs
+ 	<returnTypeC: #'char *'>
+ 	<var: #routinePrefix type: #'char *'>
  	^self trampolineName: routinePrefix numArgs: numArgs limit: NumSendTrampolines - 2!

Item was changed:
  ----- Method: Cogit>>trampolineName:numRegArgs: (in category 'initialization') -----
  trampolineName: routinePrefix numRegArgs: numArgs
+ 	<returnTypeC: #'char *'>
+ 	<var: #routinePrefix type: #'char *'>
  	^self trampolineName: routinePrefix numArgs: numArgs limit: self numRegArgs!

Item was changed:
  ----- Method: SpurSegmentManager>>addSegmentOfSize: (in category 'growing/shrinking memory') -----
  addSegmentOfSize: ammount
  	<returnTypeC: #'SpurSegmentInfo *'>
  	<inline: false>
  	| allocatedSize |
  	<var: #newSeg type: #'SpurSegmentInfo *'>
  	<var: #segAddress type: #'void *'>
+ 	<var: #allocatedSize type: #'usqInt'>
  	self cCode: [] inSmalltalk: [segments ifNil: [^nil]]. "bootstrap"
  	(manager "sent to the manager so that the simulator can increase memory to simulate a new segment"
  			sqAllocateMemorySegmentOfSize: ammount
  			Above: (self firstGapOfSizeAtLeast: ammount)
  			AllocatedSizeInto: (self cCode: [self addressOf: allocatedSize]
  									inSmalltalk: [[:sz| allocatedSize := sz]])) ifNotNil:
  		[:segAddress| | newSegIndex newSeg |
  		 newSegIndex := self insertSegmentFor: segAddress asUnsignedLong.
  		 newSeg := self addressOf: (segments at: newSegIndex).
  		 newSeg
  			segStart: segAddress asUnsignedLong;
  			segSize: allocatedSize.
  		 self bridgeFrom: (self addressOf: (segments at: newSegIndex - 1)) to: newSeg.
  		 self bridgeFrom: newSeg to: (newSegIndex = (numSegments - 1) ifFalse:
  										[self addressOf: (segments at: newSegIndex + 1)]).
  		 "test isInMemory:"
  		 0 to: numSegments - 1 do:
  			[:i|
  			self assert: (self isInSegments: (segments at: i) segStart).
  			self assert: (self isInSegments: (segments at: i) segLimit - manager wordSize).
  			self assert: ((self isInSegments: (segments at: i) segLimit) not
  						or: [i < (numSegments - 1)
  							and: [(segments at: i) segLimit = (segments at: i + 1) segStart]]).
  			self assert: ((self isInSegments: (segments at: i) segStart - manager wordSize) not
  							or: [i > 0
  								and: [(segments at: i - 1) segLimit = (segments at: i) segStart]])].
  		 ^newSeg].
  	^nil!



More information about the Vm-dev mailing list