Eliot Miranda uploaded a new version of VMMaker to project VM Maker: http://source.squeak.org/VMMaker/VMMaker.oscog-eem.2649.mcz ==================== Summary ==================== Name: VMMaker.oscog-eem.2649 Author: eem Time: 30 December 2019, 7:25:12.571432 pm UUID: b9c447b7-95f3-471f-9235-c30a764b9281 Ancestors: VMMaker.oscog-eem.2648 SImulation: Nil localFP when entering the CoInterpreter through a run-time call. Add a flag so that run-time calls can be leak checked. C;lean ups to printing so that the CogOopOnspector doesn't get interrupted with halts and doesn't see "VMObjectProxy for" noise. Abstract forwarder printing, and use it when printing a dead object in new space (a forwarded corpse). =============== Diff against VMMaker.oscog-eem.2648 =============== Item was changed: ----- Method: CoInterpreter>>assertValidExternalStackPointers (in category 'debug support') ----- assertValidExternalStackPointers + "For use *ONLY* by routines coming in to the VM, + i.e. handleCallOrJumpSimulationTrap:. This is because it nils localFP as a side-effect." self assert: framePointer < stackPage baseAddress. self assert: stackPointer < framePointer. self assert: framePointer > stackPointer. + self assert: stackPointer >= (stackPage realStackLimit - self stackLimitOffset). + localFP := nil! - self assert: stackPointer >= (stackPage realStackLimit - self stackLimitOffset)! Item was changed: ----- Method: Cogit>>handleCallOrJumpSimulationTrap: (in category 'simulation only') ----- handleCallOrJumpSimulationTrap: aProcessorSimulationTrap <doNotGenerate> | evaluable function memory result savedFramePointer savedStackPointer savedArgumentCount leaf retpc | + objectMemory maybeLeakCheckForRuntimeCall. evaluable := simulatedTrampolines at: aProcessorSimulationTrap address ifAbsent: [self errorProcessingSimulationTrap: aProcessorSimulationTrap in: simulatedTrampolines]. function := evaluable isBlock ifTrue: ['aBlock; probably some plugin primitive'] ifFalse: [evaluable receiver == backEnd ifTrue: [^self handleABICallOrJumpSimulationTrap: aProcessorSimulationTrap evaluable: evaluable]. evaluable selector]. function ~~ #ceBaseFrameReturn: ifTrue: [coInterpreter assertValidExternalStackPointers]. (backEnd wantsNearAddressFor: function) ifTrue: [^self perform: function with: aProcessorSimulationTrap]. memory := coInterpreter memory. aProcessorSimulationTrap type == #call ifTrue: [(leaf := coInterpreter mcprims includes: function) ifTrue: [processor simulateLeafCallOf: aProcessorSimulationTrap address nextpc: aProcessorSimulationTrap nextpc memory: memory. retpc := processor leafRetpcIn: memory] ifFalse: [processor simulateCallOf: aProcessorSimulationTrap address nextpc: aProcessorSimulationTrap nextpc memory: memory. retpc := processor retpcIn: memory]. self recordInstruction: {'(simulated call of '. aProcessorSimulationTrap address. '/'. function. ')'}] ifFalse: [leaf := false. processor simulateJumpCallOf: aProcessorSimulationTrap address memory: memory. retpc := processor retpcIn: memory. "sideways call; the primitive has pushed a return address." self recordInstruction: {'(simulated jump to '. aProcessorSimulationTrap address. '/'. function. ')'}]. savedFramePointer := coInterpreter framePointer. savedStackPointer := coInterpreter stackPointer. savedArgumentCount := coInterpreter argumentCount. result := ["self halt: evaluable selector." clickConfirm ifTrue: [(self confirm: 'skip run-time call?') ifFalse: [clickConfirm := false. self halt]]. evaluable valueWithArguments: (processor postCallArgumentsNumArgs: evaluable numArgs in: memory)] on: ReenterMachineCode do: [:ex| ex return: ex returnValue]. coInterpreter assertValidExternalStackPointers. + objectMemory maybeLeakCheckForRuntimeCall. "Verify the stack layout assumption compileInterpreterPrimitive: makes, provided we've not called something that has built a frame, such as closure value or evaluate method, or switched frames, such as primitiveSignal, primitiveWait, primitiveResume, primitiveSuspend et al." (function beginsWith: 'primitive') ifTrue: [coInterpreter checkForLastObjectOverwrite. coInterpreter primFailCode = 0 ifTrue: [(#( primitiveClosureValue primitiveClosureValueWithArgs primitiveClosureValueNoContextSwitch primitiveFullClosureValue primitiveFullClosureValueWithArgs primitiveFullClosureValueNoContextSwitch primitiveSignal primitiveWait primitiveResume primitiveSuspend primitiveYield primitiveExecuteMethodArgsArray primitiveExecuteMethod primitivePerform primitivePerformWithArgs primitivePerformInSuperclass primitiveTerminateTo primitiveStoreStackp primitiveDoPrimitiveWithArgs) includes: function) ifFalse: ["This is a rare case (e.g. in Scorch where a married context's sender is set to nil on trapTrpped and hence the stack layout is altered." (function == #primitiveSlotAtPut and: [objectMemory isContext: (coInterpreter frameReceiver: coInterpreter framePointer)]) ifFalse: [self assert: savedFramePointer = coInterpreter framePointer. self assert: savedStackPointer + (savedArgumentCount * objectMemory wordSize) = coInterpreter stackPointer]]] ifFalse: [self assert: savedFramePointer = coInterpreter framePointer. self assert: savedStackPointer = coInterpreter stackPointer]]. result ~~ #continueNoReturn ifTrue: [self recordInstruction: {'(simulated return to '. processor retpcIn: memory. ')'}. leaf ifTrue: [processor simulateLeafReturnIn: memory] ifFalse: [processor simulateReturnIn: memory]. self assert: processor pc = retpc. processor smashCallerSavedRegistersWithValuesFrom: 16r80000000 by: objectMemory wordSize in: memory]. self assert: (result isInteger "an oop result" or: [result == coInterpreter or: [result == objectMemory or: [#(nil continue continueNoReturn) includes: result]]]). processor cResultRegister: (result ifNil: [0] ifNotNil: [result isInteger ifTrue: [result] ifFalse: [16rF00BA222]]) "coInterpreter cr. processor sp + 32 to: processor sp - 32 by: -4 do: [:sp| sp = processor sp ifTrue: [coInterpreter print: 'sp->'; tab] ifFalse: [coInterpreter printHex: sp]. coInterpreter tab; printHex: (coInterpreter longAt: sp); cr]"! Item was added: + ----- Method: NewObjectMemory>>leakCheckRuntimeCalls (in category 'debug support') ----- + leakCheckRuntimeCalls + <doNotGenerate> + ^(checkForLeaks bitAnd: 32) ~= 0! Item was added: + ----- Method: NewObjectMemory>>maybeLeakCheckForRuntimeCall (in category 'debug support') ----- + maybeLeakCheckForRuntimeCall + <doNotGenerate> + (checkForLeaks bitAnd: 32) ~= 0 ifTrue: + [coInterpreter runLeakChecker]! Item was changed: ----- Method: NewObjectMemory>>setCheckForLeaks: (in category 'debug support') ----- setCheckForLeaks: integerFlags + " 0 = do nothing. + 1 = check for leaks on fullGC (GCModeFull). + 2 = check for leaks on scavenger (GCModeNewSpace). + 4 = check for leaks on incremental (GCModeIncremental) + 8 = check for leaks on become (GCModeBecome) + 16 = check for leaks on image segments (GCModeImageSegment) + 32 = check for leaks on simulated run-time call." - "0 = do nothing. - 1 = check for leaks on fullGC. - 2 = check for leaks on incrementalGC. - 8 = check for leaks on become" checkForLeaks := integerFlags! Item was added: + ----- Method: SpurMemoryManager>>leakCheckRuntimeCalls (in category 'debug support') ----- + leakCheckRuntimeCalls + <doNotGenerate> + ^(checkForLeaks bitAnd: 32) ~= 0! Item was added: + ----- Method: SpurMemoryManager>>maybeLeakCheckForRuntimeCall (in category 'debug support') ----- + maybeLeakCheckForRuntimeCall + <doNotGenerate> + (checkForLeaks bitAnd: 32) ~= 0 ifTrue: + [coInterpreter runLeakChecker]! Item was changed: ----- Method: SpurMemoryManager>>setCheckForLeaks: (in category 'spur bootstrap') ----- setCheckForLeaks: integerFlags " 0 = do nothing. 1 = check for leaks on fullGC (GCModeFull). 2 = check for leaks on scavenger (GCModeNewSpace). 4 = check for leaks on incremental (GCModeIncremental) 8 = check for leaks on become (GCModeBecome) + 16 = check for leaks on image segments (GCModeImageSegment) + 32 = check for leaks on simulated run-time call." - 16 = check for leaks on image segments (GCModeImageSegment)" checkForLeaks := integerFlags! Item was changed: ----- Method: StackInterpreter>>printActivationNameFor:receiver:isBlock:firstTemporary: (in category 'debug printing') ----- printActivationNameFor: aMethod receiver: anObject isBlock: isBlock firstTemporary: maybeMessage | methClass methodSel classObj | <inline: false> isBlock ifTrue: [self print: '[] in ']. methClass := self findClassOfMethod: aMethod forReceiver: anObject. methodSel := self findSelectorOfMethod: aMethod. ((objectMemory addressCouldBeOop: anObject) and: [(objectMemory isOopForwarded: anObject) not and: [self addressCouldBeClassObj: (classObj := objectMemory fetchClassOf: anObject)]]) ifTrue: [(classObj = methClass or: [methClass isNil or: [methClass = objectMemory nilObject] "i.e. doits"]) ifTrue: [self printNameOfClass: classObj count: 5] ifFalse: [self printNameOfClass: classObj count: 5. self print: '('. self printNameOfClass: methClass count: 5. self print: ')']] ifFalse: + [self print: 'INVALID RECEIVER']. - [self cCode: '' inSmalltalk: [self halt]. - self print: 'INVALID RECEIVER']. self print: '>'. (objectMemory addressCouldBeOop: methodSel) ifTrue: [methodSel = objectMemory nilObject ifTrue: [self print: '(nil)'] ifFalse: [self printStringOf: methodSel]] ifFalse: [self print: 'INVALID SELECTOR']. (methodSel = (objectMemory splObj: SelectorDoesNotUnderstand) and: [(objectMemory addressCouldBeObj: maybeMessage) and: [(objectMemory fetchClassOfNonImm: maybeMessage) = (objectMemory splObj: ClassMessage)]]) ifTrue: ["print arg message selector" methodSel := objectMemory fetchPointer: MessageSelectorIndex ofObject: maybeMessage. self print: ' '. self printStringOf: methodSel]! Item was added: + ----- Method: StackInterpreter>>printForwarder: (in category 'debug printing') ----- + printForwarder: oop + <inline: false> + self + print: ' is a forwarded object to '; printHex: (objectMemory followForwarded: oop); + print: ' of slot size '; printNum: (objectMemory numSlotsOfAny: oop). + objectMemory printHeaderTypeOf: oop. + self cr! Item was changed: ----- Method: StackInterpreter>>printOop: (in category 'debug printing') ----- printOop: oop | cls fmt lastIndex startIP bytecodesPerLine column | <inline: false> (objectMemory isImmediate: oop) ifTrue: [^self shortPrintOop: oop]. self printHex: oop. (objectMemory addressCouldBeObj: oop) ifFalse: + [(oop bitAnd: objectMemory allocationUnit - 1) ~= 0 ifTrue: [^self print: ' is misaligned'; cr]. + ((objectMemory isInNewSpace: oop) + and: [objectMemory isForwarded: oop]) ifTrue: + [self printForwarder: oop]. + ^self print: (self whereIs: oop); cr]. - [^self print: ((oop bitAnd: objectMemory allocationUnit - 1) ~= 0 - ifTrue: [' is misaligned'] - ifFalse: [self whereIs: oop]); cr]. (objectMemory isFreeObject: oop) ifTrue: [self print: ' is a free chunk of size '; printNum: (objectMemory sizeOfFree: oop). objectMemory hasSpurMemoryManagerAPI ifTrue: [self print: ' 0th: '; printHex: (objectMemory fetchPointer: 0 ofFreeChunk: oop). objectMemory printHeaderTypeOf: oop]. ^self cr]. (objectMemory isForwarded: oop) ifTrue: + [^self printForwarder: oop]. - [self - print: ' is a forwarded object to '; printHex: (objectMemory followForwarded: oop); - print: ' of slot size '; printNum: (objectMemory numSlotsOfAny: oop). - objectMemory printHeaderTypeOf: oop. - ^self cr]. self print: ': a(n) '. self printNameOfClass: (cls := objectMemory fetchClassOfNonImm: oop) count: 5. cls = (objectMemory splObj: ClassFloat) ifTrue: [^self cr; printFloat: (objectMemory dbgFloatValueOf: oop); cr]. fmt := objectMemory formatOf: oop. fmt > objectMemory lastPointerFormat ifTrue: [self print: ' nbytes '; printNum: (objectMemory numBytesOf: oop)]. self cr. (fmt between: objectMemory firstLongFormat and: objectMemory firstCompiledMethodFormat - 1) ifTrue: ["This will answer false if splObj: ClassAlien is nilObject" (self is: oop KindOfClass: (objectMemory splObj: ClassAlien)) ifTrue: [self print: ' datasize '; printNum: (self sizeOfAlienData: oop). self print: ((self isIndirectAlien: oop) ifTrue: [' indirect @ '] ifFalse: [(self isPointerAlien: oop) ifTrue: [' pointer @ '] ifFalse: [' direct @ ']]). ^self printHex: (self startOfAlienData: oop) asUnsignedInteger; cr]. (objectMemory isWordsNonImm: oop) ifTrue: [lastIndex := 64 min: ((objectMemory numBytesOf: oop) / objectMemory wordSize). lastIndex > 0 ifTrue: [1 to: lastIndex do: [:index| self space; printHex: (self cCoerceSimple: (objectMemory fetchLong32: index - 1 ofObject: oop) to: #'unsigned int'). (index \\ self elementsPerPrintOopLine) = 0 ifTrue: [self cr]]. (lastIndex \\ self elementsPerPrintOopLine) = 0 ifFalse: [self cr]]. ^self]. ^self printStringOf: oop; cr]. "this is nonsense. apologies." startIP := (objectMemory lastPointerOf: oop) + objectMemory bytesPerOop - objectMemory baseHeaderSize / objectMemory bytesPerOop. lastIndex := 256 min: startIP. lastIndex > 0 ifTrue: [1 to: lastIndex do: [:index| self cCode: [self printHex: (objectMemory fetchPointer: index - 1 ofObject: oop); space] inSmalltalk: [self space; printHex: (objectMemory fetchPointer: index - 1 ofObject: oop); space. self print: (self shortPrint: (objectMemory fetchPointer: index - 1 ofObject: oop))]. (index \\ self elementsPerPrintOopLine) = 0 ifTrue: [self cr]]. (lastIndex \\ self elementsPerPrintOopLine) = 0 ifFalse: [self cr]]. (objectMemory isCompiledMethod: oop) ifFalse: [startIP > 64 ifTrue: [self print: '...'; cr]] ifTrue: [startIP := startIP * objectMemory wordSize + 1. lastIndex := objectMemory lengthOf: oop. lastIndex - startIP > 100 ifTrue: [lastIndex := startIP + 100]. bytecodesPerLine := 8. column := 1. startIP to: lastIndex do: [:index| | byte | column = 1 ifTrue: [self cCode: 'printf("0x%08" PRIxSQPTR ": ", (usqIntptr_t)(oop+BaseHeaderSize+index-1))' inSmalltalk: [self print: (oop+objectMemory baseHeaderSize+index-1) hex; print: ': ']]. byte := objectMemory fetchByte: index - 1 ofObject: oop. self cCode: 'printf(" %02x/%-3d", (int)byte,(int)byte)' inSmalltalk: [self space; print: (byte radix: 16); printChar: $/; printNum: byte]. column := column + 1. column > bytecodesPerLine ifTrue: [column := 1. self cr]]. column = 1 ifFalse: [self cr]]! Item was changed: ----- Method: VMCompiledMethodProxy>>literalAt: (in category 'literals') ----- literalAt: index ^VMObjectProxy new for: (coInterpreter literal: index - 1 ofMethod: oop) coInterpreter: coInterpreter + objectMemory: objectMemory; + printPretty: printPretty; + yourself! - objectMemory: objectMemory! Item was changed: Object subclass: #VMObjectProxy + instanceVariableNames: 'coInterpreter oop objectMemory printPretty' - instanceVariableNames: 'coInterpreter oop objectMemory' classVariableNames: '' poolDictionaries: '' category: 'VMMaker-Support'! !VMObjectProxy commentStamp: 'eem 8/6/2014 14:46' prior: 0! A VMObjectProxy is a wraper for an oop in the VM, that provides limited access to that oop as an object. ! Item was changed: + ----- Method: VMObjectProxy>>for:coInterpreter:objectMemory: (in category 'initialization') ----- - ----- Method: VMObjectProxy>>for:coInterpreter:objectMemory: (in category 'initialize-release') ----- for: aCompiledMethodOop coInterpreter: aCoInterpreter objectMemory: anObjectMemory oop := aCompiledMethodOop. coInterpreter := aCoInterpreter. + objectMemory := anObjectMemory. + printPretty := false! - objectMemory := anObjectMemory! Item was changed: ----- Method: VMObjectProxy>>printOn: (in category 'printing') ----- printOn: aStream | shortPrint | + printPretty ifTrue: + [[aStream nextPutAll: (coInterpreter shortPrint: oop)] + on: Error + do: [:ex| oop printOn: aStream base: 16]. + ^self]. shortPrint := [coInterpreter shortPrint: oop] on: Error do: [:ex| ^super printOn: aStream]. super printOn: aStream. shortPrint first = $= ifTrue: [shortPrint := shortPrint allButFirst]. aStream nextPutAll: ' for '; nextPutAll: shortPrint! Item was added: + ----- Method: VMObjectProxy>>printPretty (in category 'accessing') ----- + printPretty + ^printPretty! Item was added: + ----- Method: VMObjectProxy>>printPretty: (in category 'accessing') ----- + printPretty: aBoolean + printPretty := aBoolean! |
Free forum by Nabble | Edit this page |