Eliot Miranda uploaded a new version of VMMaker to project VM Maker: http://source.squeak.org/VMMaker/VMMaker.oscog-eem.2720.mcz ==================== Summary ==================== Name: VMMaker.oscog-eem.2720 Author: eem Time: 24 February 2020, 9:57:51.683539 am UUID: 36860558-04f0-4fda-b52f-062b2386286d Ancestors: VMMaker.oscog-eem.2719 Cogit: Change return value for not-found of methodFor: from 0 to nil. #define codeToDataDelta as 0 for the non DUAL_MAPPED_CODE_ZONE regime. Fix followForwardedLiteralsIn:, mapObjectReferencesInMachineCodeForXXX, and storeLiteral:atAnnotatedAddress:using: for the DUAL_MAPPED_CODE_ZONE regime. Inlcude the method in question in armPrintDualZoneAnomalies output. Fix printMethodFieldForPrintContext: to always print the method oop frst and the cogMethod, if any, afterwards. Fix asserts in frameCallerContext: and mapStackPages when a frame context may be forwarded as part of scavenging. Slang: Fix sizeOfIntegralCType: for the more complex defnition of codeToDataDelta. =============== Diff against VMMaker.oscog-eem.2719 =============== Item was changed: ----- Method: CCodeGenerator>>sizeOfIntegralCType: (in category 'inlining') ----- sizeOfIntegralCType: anIntegralCType "<String>" "N.B. Only works for values for which isIntegralCType: answers true." | prunedCType index | - (anIntegralCType beginsWith: 'register ') ifTrue: - [^self sizeOfIntegralCType: (anIntegralCType allButFirst: 9)]. prunedCType := (anIntegralCType beginsWith: 'unsigned ') ifTrue: [(anIntegralCType allButFirst: 9) withBlanksTrimmed] ifFalse: [(anIntegralCType beginsWith: 'signed ') ifTrue: [(anIntegralCType allButFirst: 7) withBlanksTrimmed] ifFalse: [anIntegralCType]]. ^prunedCType asString caseOf: { ['sqLong'] -> [8]. ['usqLong'] -> [8]. ['long long'] -> [8]. ['sqInt'] -> [BytesPerOop]. ['usqInt'] -> [BytesPerOop]. ['sqIntptr_t'] -> [BytesPerWord]. ['usqIntptr_t'] -> [BytesPerWord]. ['int'] -> [4]. ['short'] -> [2]. ['short int'] -> [2]. ['char'] -> [1]. ['long'] -> [BytesPerWord]. "It's ambiguous on LLP64 and we'll later remove it" ['size_t'] -> [BytesPerWord]. ['pid_t'] -> [BytesPerWord]. } otherwise: + [(anIntegralCType beginsWith: 'register ') ifTrue: + [^self sizeOfIntegralCType: (anIntegralCType allButFirst: 9)]. + (anIntegralCType beginsWith: 'static ') ifTrue: + [^self sizeOfIntegralCType: (anIntegralCType allButFirst: 7)]. + ((anIntegralCType beginsWith: 'unsigned') "e.g. 'unsigned : 8'" - [((anIntegralCType beginsWith: 'unsigned') "e.g. 'unsigned : 8'" and: [(anIntegralCType includesAnyOf: '[*]') not + and: [(index := anIntegralCType indexOf: $:) > 0]]) ifTrue: + [^(Integer readFrom: (anIntegralCType copyFrom: index + 1 to: anIntegralCType size) withBlanksTrimmed readStream) + 7 // 8]. + anIntegralCType first = $# ifTrue: + [(anIntegralCType subStrings: '\') do: + [:substring| + substring first ~~ $# ifTrue: + [([self sizeOfIntegralCType: substring withBlanksTrimmed] + on: Error + do: [:ex| nil]) ifNotNil: [:size| ^size]]]]. + self error: 'unrecognized integral type']! - and: [(index := anIntegralCType indexOf: $:) > 0]]) - ifTrue: [(Integer readFrom: (anIntegralCType copyFrom: index + 1 to: anIntegralCType size) withBlanksTrimmed readStream) + 7 // 8] - ifFalse: [self error: 'unrecognized integral type']]! Item was changed: ----- Method: CoInterpreter>>checkOkayFields: (in category 'debug support') ----- checkOkayFields: oop "Check if the argument is an ok object. If this is a pointers object, check that its fields are all okay oops." | hasYoung i fieldOop | (oop = nil or: [oop = 0]) ifTrue: [ ^true ]. "?? eem 1/16/2013" (objectMemory isIntegerObject: oop) ifTrue: [ ^true ]. (objectMemory checkOkayOop: oop) ifFalse: [ ^false ]. (objectMemory checkOopHasOkayClass: oop) ifFalse: [ ^false ]. ((objectMemory isPointersNonImm: oop) or: [objectMemory isCompiledMethod: oop]) ifFalse: [ ^true ]. hasYoung := objectMemory hasSpurMemoryManagerAPI not and: [objectMemory isYoungObject: (objectMemory fetchClassOfNonImm: oop)]. (objectMemory isCompiledMethod: oop) ifTrue: [i := (objectMemory literalCountOf: oop) + LiteralStart - 1] ifFalse: [(objectMemory isContext: oop) ifTrue: [i := CtxtTempFrameStart + (self fetchStackPointerOf: oop) - 1] ifFalse: [i := (objectMemory lengthOf: oop) - 1]]. [i >= 0] whileTrue: [fieldOop := objectMemory fetchPointer: i ofObject: oop. (objectMemory isNonIntegerObject: fieldOop) ifTrue: [(i = 0 and: [objectMemory isCompiledMethod: oop]) ifTrue: + [(cogMethodZone methodFor: (self pointerForOop: fieldOop)) ifNil: - [(cogMethodZone methodFor: (self pointerForOop: fieldOop)) = 0 ifTrue: [self print: 'method '; printHex: oop; print: ' has an invalid cog method reference'. ^false]] ifFalse: [hasYoung := hasYoung or: [objectMemory isYoung: fieldOop]. (objectMemory checkOkayOop: fieldOop) ifFalse: [ ^false ]. (self checkOopHasOkayClass: fieldOop) ifFalse: [ ^false ]]]. i := i - 1]. hasYoung ifTrue: [^objectMemory checkOkayYoungReferrer: oop]. ^true! Item was changed: ----- Method: CoInterpreter>>frameCallerContext: (in category 'frame access') ----- frameCallerContext: theFP "In the StackInterpreter the saved ip field of a base frame holds the base frame's caller context. But in the Cog VM the first word on the stack holds the base frame's caller context, which is immediately above the stacked receiver." <var: #theFP type: #'char *'> | thePage callerContextOrNil | <var: #thePage type: #'StackPage *'> self assert: (self isBaseFrame: theFP). thePage := stackPages stackPageFor: theFP. callerContextOrNil := stackPages longAt: thePage baseAddress. self assert: (objectMemory addressCouldBeObj: callerContextOrNil). + self assert: (callerContextOrNil = objectMemory nilObject or: [objectMemory isContext: (objectMemory followMaybeForwarded: callerContextOrNil)]). - self assert: (callerContextOrNil = objectMemory nilObject or: [objectMemory isContext: callerContextOrNil]). ^callerContextOrNil! Item was changed: ----- Method: CoInterpreter>>mapStackPages (in category 'object memory support') ----- mapStackPages <inline: #never> <var: #thePage type: #'StackPage *'> <var: #theSP type: #'char *'> <var: #theFP type: #'char *'> <var: #frameRcvrOffset type: #'char *'> <var: #callerFP type: #'char *'> <var: #theIPPtr type: #'char *'> | numLivePages | numLivePages := 0. 0 to: numStackPages - 1 do: [:i| | thePage theSP theFP frameRcvrOffset callerFP theIPPtr theIP oop | thePage := stackPages stackPageAt: i. thePage isFree ifFalse: [self assert: (self ifCurrentStackPageHasValidHeadPointers: thePage). numLivePages := numLivePages + 1. theSP := thePage headSP. theFP := thePage headFP. "Skip the instruction pointer on top of stack of inactive pages." thePage = stackPage ifTrue: [theIPPtr := ((self isMachineCodeFrame: theFP) or: [(self iframeSavedIP: theFP) = 0]) ifTrue: [0] ifFalse: [theFP + FoxIFSavedIP]] ifFalse: [theIPPtr := theSP. theSP := theSP + objectMemory wordSize]. [self assert: (thePage addressIsInPage: theFP). self assert: (thePage addressIsInPage: theSP). self assert: (theIPPtr = 0 or: [thePage addressIsInPage: theIPPtr]). frameRcvrOffset := self frameReceiverLocation: theFP. [theSP <= frameRcvrOffset] whileTrue: [oop := stackPages longAt: theSP. (objectMemory shouldRemapOop: oop) ifTrue: [stackPages longAt: theSP put: (objectMemory remapObj: oop)]. theSP := theSP + objectMemory wordSize]. (self frameHasContext: theFP) ifTrue: [(objectMemory shouldRemapObj: (self frameContext: theFP)) ifTrue: [stackPages longAt: theFP + FoxThisContext put: (objectMemory remapObj: (self frameContext: theFP))]. "With SqueakV3 objectMemory or SpurPlanningCompactor can't assert since object body is yet to move." (objectMemory hasSpurMemoryManagerAPI + and: [(objectMemory slidingCompactionInProgress or: [objectMemory scavengeInProgress]) not]) ifTrue: - and: [objectMemory slidingCompactionInProgress not]) ifTrue: [self assert: ((self isMarriedOrWidowedContext: (self frameContext: theFP)) and: [(self frameOfMarriedContext: (self frameContext: theFP)) = theFP])]]. (self isMachineCodeFrame: theFP) ifFalse: [(objectMemory shouldRemapObj: (self iframeMethod: theFP)) ifTrue: [theIPPtr ~= 0 ifTrue: [theIP := stackPages longAt: theIPPtr. theIP = cogit ceReturnToInterpreterPC ifTrue: [self assert: (self iframeSavedIP: theFP) > (self iframeMethod: theFP). theIPPtr := theFP + FoxIFSavedIP. theIP := stackPages longAt: theIPPtr] ifFalse: [self assert: theIP > (self iframeMethod: theFP)]. theIP := theIP - (self iframeMethod: theFP)]. stackPages longAt: theFP + FoxMethod put: (objectMemory remapObj: (self iframeMethod: theFP)). theIPPtr ~= 0 ifTrue: [stackPages longAt: theIPPtr put: theIP + (self iframeMethod: theFP)]]]. (callerFP := self frameCallerFP: theFP) ~= 0] whileTrue: [theSP := (theIPPtr := theFP + FoxCallerSavedIP) + objectMemory wordSize. theFP := callerFP]. theSP := theFP + FoxCallerSavedIP + objectMemory wordSize. [theSP <= thePage baseAddress] whileTrue: [oop := stackPages longAt: theSP. (objectMemory shouldRemapOop: oop) ifTrue: [stackPages longAt: theSP put: (objectMemory remapObj: oop)]. theSP := theSP + objectMemory wordSize]]]. stackPages recordLivePagesOnMapping: numLivePages! Item was changed: ----- Method: CoInterpreter>>printMethodFieldForPrintContext: (in category 'debug printing') ----- printMethodFieldForPrintContext: aContext <inline: true> | meth | meth := objectMemory fetchPointer: MethodIndex ofObject: aContext. + self printOopShortInner: meth. + (self methodHasCogMethod: meth) ifTrue: + [self space; print: '('; printHexnp: (self cogMethodOf: meth); print: ')']. + self cr! - (self isMarriedOrWidowedContext: aContext) - ifFalse: - [self printOopShortInner: meth. - (self methodHasCogMethod: meth) ifTrue: - [self space; print: '('; printHexnp: (self cogMethodOf: meth); print: ')']. - self cr] - ifTrue: - [(self methodHasCogMethod: meth) ifTrue: - [self printHexnp: (self cogMethodOf: meth); space]. - self shortPrintOop: meth]! Item was changed: ----- Method: CoInterpreter>>printMethodHeaderOop: (in category 'debug printing') ----- printMethodHeaderOop: anOop "Print the CogMethod and its header if this is a CogMethod reference." - | cogMethod | <var: #cogMethod type: #'CogMethod *'> (self isCogMethodReference: anOop) ifTrue: + [(cogMethodZone methodFor: (self pointerForOop: anOop)) ifNotNil: + [:cogMethod| ^self printHex: anOop; space; printDecodeMethodHeaderOop: cogMethod methodHeader]]. - [cogMethod := cogMethodZone methodFor: (self pointerForOop: anOop). - cogMethod ~= 0 ifTrue: - [^self printHex: anOop; space; printDecodeMethodHeaderOop: cogMethod methodHeader]]. ^self printDecodeMethodHeaderOop: anOop! Item was changed: ----- Method: CogMethodZone>>methodFor: (in category 'jit - api') ----- methodFor: address <api> <returnTypeC: #'CogMethod *'> <var: #address type: #'void *'> | cogMethod nextMethod | - <var: #cogMethod type: #'CogMethod *'> - <var: #nextMethod type: #'CogMethod *'> cogMethod := coInterpreter cCoerceSimple: baseAddress to: #'CogMethod *'. [cogMethod < self limitZony and: [cogMethod asUnsignedInteger <= address asUnsignedInteger]] whileTrue: [nextMethod := self methodAfter: cogMethod. nextMethod = cogMethod ifTrue: + [^nil]. - [^0]. (address asUnsignedInteger >= cogMethod asUnsignedInteger and: [address asUnsignedInteger < nextMethod asUnsignedInteger]) ifTrue: [^cogMethod]. cogMethod := nextMethod]. + ^nil! - ^0! Item was changed: ----- Method: Cogit class>>declareCVarsIn: (in category 'translation') ----- declareCVarsIn: aCCodeGenerator | backEnd | backEnd := CogCompilerClass basicNew. #( 'coInterpreter' 'objectMemory' 'methodZone' 'objectRepresentation' 'cogBlockMethodSurrogateClass' 'cogMethodSurrogateClass' 'nsSendCacheSurrogateClass' 'threadManager' 'processor' 'lastNInstructions' 'simulatedAddresses' 'simulatedTrampolines' 'simulatedVariableGetters' 'simulatedVariableSetters' 'processorFrameValid' 'printRegisters' 'printInstructions' 'clickConfirm' 'singleStep') do: [:simulationVariableNotNeededForRealVM| aCCodeGenerator removeVariable: simulationVariableNotNeededForRealVM]. NewspeakVM ifFalse: [#( 'selfSendTrampolines' 'dynamicSuperSendTrampolines' 'implicitReceiverSendTrampolines' 'outerSendTrampolines' 'ceEnclosingObjectTrampoline' 'numIRCs' 'indexOfIRC' 'theIRCs') do: [:variableNotNeededInNormalVM| aCCodeGenerator removeVariable: variableNotNeededInNormalVM]]. aCCodeGenerator removeConstant: #COGMTVM. "this should be defined at compile time" aCCodeGenerator addHeaderFile:'<stddef.h>'; "for e.g. offsetof" addHeaderFile:'"sqCogStackAlignment.h"'; addHeaderFile:'"dispdbg.h"'; "must precede cointerp.h & cogit.h otherwise NoDbgRegParms gets screwed up" addHeaderFile:'"cogmethod.h"'. NewspeakVM ifTrue: [aCCodeGenerator addHeaderFile:'"nssendcache.h"']. aCCodeGenerator addHeaderFile:'#if COGMTVM'; addHeaderFile:'"cointerpmt.h"'; addHeaderFile:'#else'; addHeaderFile:'"cointerp.h"'; addHeaderFile:'#endif'; addHeaderFile:'"cogit.h"'. aCCodeGenerator var: #ceGetFP declareC: 'usqIntptr_t (*ceGetFP)(void)'; var: #ceGetSP declareC: 'usqIntptr_t (*ceGetSP)(void)'; var: #ceCaptureCStackPointers declareC: 'void (*ceCaptureCStackPointers)(void)'; var: #ceEnterCogCodePopReceiverReg declareC: 'void (*ceEnterCogCodePopReceiverReg)(void)'; var: #realCEEnterCogCodePopReceiverReg declareC: 'void (*realCEEnterCogCodePopReceiverReg)(void)'; var: #ceCallCogCodePopReceiverReg declareC: 'void (*ceCallCogCodePopReceiverReg)(void)'; var: #realCECallCogCodePopReceiverReg declareC: 'void (*realCECallCogCodePopReceiverReg)(void)'; var: #ceCallCogCodePopReceiverAndClassRegs declareC: 'void (*ceCallCogCodePopReceiverAndClassRegs)(void)'; var: #realCECallCogCodePopReceiverAndClassRegs declareC: 'void (*realCECallCogCodePopReceiverAndClassRegs)(void)'; var: #postCompileHook declareC: 'void (*postCompileHook)(CogMethod *)'; var: #openPICList declareC: 'CogMethod *openPICList = 0'; var: #maxMethodBefore type: #'CogBlockMethod *'; var: 'enumeratingCogMethod' type: #'CogMethod *'. aCCodeGenerator var: #ceTryLockVMOwner declareC: '#if COGMTVM\usqIntptr_t (*ceTryLockVMOwner)(void)'; var: #ceUnlockVMOwner declareC: 'void (*ceUnlockVMOwner)(void)\#endif /* COGMTVM */'. backEnd numCheckLZCNTOpcodes > 0 ifTrue: [aCCodeGenerator var: #ceCheckLZCNTFunction declareC: 'static usqIntptr_t (*ceCheckLZCNTFunction)(void)']. backEnd numCheckFeaturesOpcodes > 0 ifTrue: [aCCodeGenerator var: #ceCheckFeaturesFunction declareC: 'static usqIntptr_t (*ceCheckFeaturesFunction)(void)']. backEnd numICacheFlushOpcodes > 0 ifTrue: [aCCodeGenerator var: #ceFlushICache declareC: 'static void (*ceFlushICache)(usqIntptr_t from, usqIntptr_t to)']. aCCodeGenerator var: #ceFlushDCache + declareC: '#if DUAL_MAPPED_CODE_ZONE\static void (*ceFlushDCache)(usqIntptr_t from, usqIntptr_t to)\#endif'; + var: #codeToDataDelta + declareC: '#if DUAL_MAPPED_CODE_ZONE\static sqInt codeToDataDelta\#else\# define codeToDataDelta 0\#endif'. - declareC: '#if DUAL_MAPPED_CODE_ZONE\static void (*ceFlushDCache)(usqIntptr_t from, usqIntptr_t to)\#endif'. aCCodeGenerator declareVar: 'aMethodLabel' type: #'AbstractInstruction'; "Has to come lexicographically before backEnd & methodLabel" var: #backEnd declareC: 'AbstractInstruction * const backEnd = &aMethodLabel'; var: #methodLabel declareC: 'AbstractInstruction * const methodLabel = &aMethodLabel'. self declareC: #(abstractOpcodes stackCheckLabel blockEntryLabel blockEntryNoContextSwitch stackOverflowCall sendMiss entry noCheckEntry selfSendEntry dynSuperEntry fullBlockNoContextSwitchEntry fullBlockEntry picMNUAbort picInterpretAbort endCPICCase0 endCPICCase1 cPICEndOfCodeLabel) as: #'AbstractInstruction *' in: aCCodeGenerator. aCCodeGenerator declareVar: #cPICPrototype type: #'CogMethod *'; declareVar: #blockStarts type: #'BlockStart *'; declareVar: #fixups type: #'BytecodeFixup *'; declareVar: #methodZoneBase type: #usqInt. aCCodeGenerator var: #ordinarySendTrampolines declareC: 'sqInt ordinarySendTrampolines[NumSendTrampolines]'; var: #superSendTrampolines declareC: 'sqInt superSendTrampolines[NumSendTrampolines]'. BytecodeSetHasDirectedSuperSend ifTrue: [aCCodeGenerator var: #directedSuperSendTrampolines declareC: 'sqInt directedSuperSendTrampolines[NumSendTrampolines]'; var: #directedSuperBindingSendTrampolines declareC: 'sqInt directedSuperBindingSendTrampolines[NumSendTrampolines]']. NewspeakVM ifTrue: [aCCodeGenerator var: #selfSendTrampolines declareC: 'sqInt selfSendTrampolines[NumSendTrampolines]'; var: #dynamicSuperSendTrampolines declareC: 'sqInt dynamicSuperSendTrampolines[NumSendTrampolines]'; var: #implicitReceiverSendTrampolines declareC: 'sqInt implicitReceiverSendTrampolines[NumSendTrampolines]'; var: #outerSendTrampolines declareC: 'sqInt outerSendTrampolines[NumSendTrampolines]']. aCCodeGenerator var: #trampolineAddresses declareC: 'static char *trampolineAddresses[NumTrampolines*2]'; var: #objectReferencesInRuntime declareC: 'static usqInt objectReferencesInRuntime[NumObjRefsInRuntime+1]'; var: #labelCounter type: #int; var: #traceFlags declareC: 'int traceFlags = 8 /* prim trace log on by default */'; var: #cStackAlignment declareC: 'const int cStackAlignment = STACK_ALIGN_BYTES'. aCCodeGenerator declareVar: #minValidCallAddress type: #'usqIntptr_t'; declareVar: #debugPrimCallStackOffset type: #'usqIntptr_t'. aCCodeGenerator vmClass generatorTable ifNotNil: [:bytecodeGenTable| aCCodeGenerator var: #generatorTable declareC: 'static BytecodeDescriptor generatorTable[', bytecodeGenTable size printString, ']', (self tableInitializerFor: bytecodeGenTable in: aCCodeGenerator)]. "In C the abstract opcode names clash with the Smalltalk generator syntactic sugar. Most of the syntactic sugar is inlined, but alas some remains. Rename the syntactic sugar to avoid the clash." (self organization listAtCategoryNamed: #'abstract instructions') do: [:s| aCCodeGenerator addSelectorTranslation: s to: 'g', (aCCodeGenerator cFunctionNameFor: s)]. aCCodeGenerator addSelectorTranslation: #halt: to: 'haltmsg'. self declareFlagVarsAsByteIn: aCCodeGenerator! Item was changed: ----- Method: Cogit>>armPrintDualZoneAnomalies (in category 'debugging') ----- armPrintDualZoneAnomalies <doNotGenerate> + | badRangeStart out | - | badRangeStart | codeToDataDelta > 0 ifTrue: + [out := coInterpreter transcript. + codeBase to: methodZone zoneEnd - 4 by: 4 do: - [codeBase to: methodZone zoneEnd - 4 by: 4 do: [:address| + (objectMemory long32At: address) = (objectMemory long32At: address + codeToDataDelta) - (objectMemory long32At: address) = (objectMemory long32At: address + codeToDataDelta) ifTrue: [badRangeStart ifNotNil: + [out - [coInterpreter transcript ensureCr; nextPutAll: 'anomaly '; nextPutAll: badRangeStart hex; nextPutAll: ' to: '; nextPutAll: (address - 4) hex; nextPutAll: ' vs '; + nextPutAll: (badRangeStart + codeToDataDelta) hex; nextPutAll: ' to: '; nextPutAll: (address + codeToDataDelta - 4) hex. + (methodZone methodFor: badRangeStart) ifNotNil: + [:cogMethod| out nextPutAll: ' (method '; nextPutAll: cogMethod address hex; nextPut: $)]. + out cr; flush]. - nextPutAll: (badRangeStart + codeToDataDelta) hex; nextPutAll: ' to: '; nextPutAll: (address + codeToDataDelta - 4) hex; - cr; flush]. badRangeStart := nil] ifFalse: [badRangeStart ifNil: [badRangeStart := address]]]. badRangeStart ifNotNil: + [out - [coInterpreter transcript ensureCr; nextPutAll: 'anomaly '; nextPutAll: badRangeStart hex; nextPutAll: ' to: '; nextPutAll: (methodZone zoneEnd - 4) hex; nextPutAll: ' vs '; + nextPutAll: (badRangeStart + codeToDataDelta) hex; nextPutAll: ' to: '; nextPutAll: (methodZone zoneEnd + codeToDataDelta - 4) hex. + (methodZone methodFor: badRangeStart) ifNotNil: + [:cogMethod| out nextPutAll: ' (method '; nextPutAll: cogMethod address hex; nextPut: $)]. + out cr; flush]]. - nextPutAll: (badRangeStart + codeToDataDelta) hex; nextPutAll: ' to: '; nextPutAll: (methodZone zoneEnd + codeToDataDelta - 4) hex; - cr; flush]]. ^nil! Item was changed: ----- Method: Cogit>>followForwardedLiteralsIn: (in category 'garbage collection') ----- followForwardedLiteralsIn: cogMethod <api> <option: #SpurObjectMemory> <var: #cogMethod type: #'CogMethod *'> + | writableCogMethod hasYoungObj hasYoungObjPtr | - | hasYoungObj hasYoungObjPtr | self assert: (cogMethod cmType ~= CMMethod or: [(objectMemory isForwarded: cogMethod methodObject) not]). + writableCogMethod := self writableMethodFor: cogMethod. hasYoungObj := objectMemory isYoung: cogMethod methodObject. (objectMemory shouldRemapOop: cogMethod selector) ifTrue: + [writableCogMethod selector: (objectMemory remapObj: cogMethod selector). - [cogMethod selector: (objectMemory remapObj: cogMethod selector). (objectMemory isYoung: cogMethod selector) ifTrue: [hasYoungObj := true]]. hasYoungObjPtr := (self addressOf: hasYoungObj put: [:val| hasYoungObj := val]) asInteger. self mapFor: cogMethod performUntil: #remapIfObjectRef:pc:hasYoung: arg: hasYoungObjPtr. hasYoungObj ifTrue: [methodZone ensureInYoungReferrers: cogMethod] + ifFalse: [writableCogMethod cmRefersToYoung: false]! - ifFalse: [cogMethod cmRefersToYoung: false]! Item was changed: ----- Method: Cogit>>lookupAddress: (in category 'disassembly') ----- lookupAddress: address <doNotGenerate> - | cogMethod | address < methodZone freeStart ifTrue: [address >= methodZoneBase ifTrue: + [(methodZone methodFor: address) ifNotNil: + [:cogMethod| - [(cogMethod := methodZone methodFor: address) ~= 0 ifTrue: - [cogMethod := self cCoerceSimple: cogMethod to: #'CogMethod *'. ^((cogMethod selector ~= objectMemory nilObject and: [objectRepresentation couldBeObject: cogMethod selector]) ifTrue: [coInterpreter stringOf: cogMethod selector] ifFalse: [cogMethod asInteger hex]), '@', ((address - cogMethod asInteger) hex allButFirst: 3)]] ifFalse: [^address = (self codeEntryFor: address) ifTrue: [self codeEntryNameFor: address]]. ^nil]. (simulatedTrampolines includesKey: address) ifTrue: [^self labelForSimulationAccessor: (simulatedTrampolines at: address)]. (simulatedVariableGetters includesKey: address) ifTrue: [^self labelForSimulationAccessor: (simulatedVariableGetters at: address)]. ^(coInterpreter lookupAddress: address) ifNil: [address = self cStackPointerAddress ifTrue: [#CStackPointer] ifFalse: [address = self cFramePointerAddress ifTrue: [#CFramePointer]]]! Item was changed: ----- Method: Cogit>>mapObjectReferencesInMachineCodeForBecome (in category 'garbage collection') ----- mapObjectReferencesInMachineCodeForBecome "Update all references to objects in machine code for a become. Unlike incrementalGC or fullGC a method that does not refer to young may refer to young as a result of the become operation. Unlike incrementalGC or fullGC the reference from a Cog method to its methodObject *must not* change since the two are two halves of the same object." + | cogMethod writableCogMethod hasYoungObj hasYoungObjPtr freedPIC | - | cogMethod hasYoungObj hasYoungObjPtr freedPIC | - <var: #cogMethod type: #'CogMethod *'> hasYoungObj := false. hasYoungObjPtr := (self addressOf: hasYoungObj put: [:val| hasYoungObj := val]) asInteger. codeModified := freedPIC := false. self mapObjectReferencesInGeneratedRuntime. cogMethod := self cCoerceSimple: methodZoneBase to: #'CogMethod *'. [cogMethod < methodZone limitZony] whileTrue: [self assert: hasYoungObj not. cogMethod cmType ~= CMFree ifTrue: [self assert: (self cogMethodDoesntLookKosher: cogMethod) = 0. + writableCogMethod := self writableMethodFor: cogMethod. + writableCogMethod selector: (objectRepresentation remapOop: cogMethod selector). - cogMethod selector: (objectRepresentation remapOop: cogMethod selector). cogMethod cmType = CMClosedPIC ifTrue: [((objectMemory isYoung: cogMethod selector) or: [self mapObjectReferencesInClosedPIC: cogMethod]) ifTrue: [freedPIC := true. methodZone freeMethod: cogMethod]] ifFalse: [(objectMemory isYoung: cogMethod selector) ifTrue: [hasYoungObj := true]. cogMethod cmType = CMMethod ifTrue: [| remappedMethod | self assert: cogMethod objectHeader = objectMemory nullHeaderForMachineCodeMethod. remappedMethod := objectRepresentation remapOop: cogMethod methodObject. remappedMethod ~= cogMethod methodObject ifTrue: [(coInterpreter methodHasCogMethod: remappedMethod) ifTrue: [self error: 'attempt to become two cogged methods']. (objectMemory withoutForwardingOn: cogMethod methodObject and: remappedMethod with: cogMethod cmUsesPenultimateLit sendToCogit: #method:hasSameCodeAs:checkPenultimate:) ifFalse: [self error: 'attempt to become cogged method into different method']. "For non-Newspeak there should ne a one-to-one mapping between bytecoded and cog methods. For Newspeak not necessarily, but only for anonymous accessors." "Only reset the method object's header if it is referring to this CogMethod." (coInterpreter rawHeaderOf: cogMethod methodObject) = cogMethod asInteger ifTrue: [coInterpreter rawHeaderOf: cogMethod methodObject put: cogMethod methodHeader. + writableCogMethod - cogMethod methodHeader: (coInterpreter rawHeaderOf: remappedMethod); methodObject: remappedMethod. coInterpreter rawHeaderOf: remappedMethod put: cogMethod asInteger] ifFalse: [self assert: (self noAssertMethodClassAssociationOf: cogMethod methodObject) = objectMemory nilObject. + writableCogMethod - cogMethod methodHeader: (coInterpreter rawHeaderOf: remappedMethod); methodObject: remappedMethod]]. (objectMemory isYoung: cogMethod methodObject) ifTrue: [hasYoungObj := true]]. self mapFor: cogMethod performUntil: #remapIfObjectRef:pc:hasYoung: arg: hasYoungObjPtr. hasYoungObj ifTrue: [methodZone ensureInYoungReferrers: cogMethod. hasYoungObj := false] ifFalse: [cogMethod cmRefersToYoung: false]]]. cogMethod := methodZone methodAfter: cogMethod]. "we /must/ prune youngReferrers here because a) the [cogMethod cmRefersToYoung: false] block could have removed a method and subsequently it could be added back, and b) we can not tolerate duplicates in the youngReferrers list." methodZone pruneYoungReferrers. freedPIC ifTrue: [self unlinkSendsToFree]. codeModified ifTrue: "After updating oops in inline caches we need to flush the icache." [backEnd flushICacheFrom: codeBase asUnsignedInteger to: methodZone limitZony asUnsignedInteger]! Item was changed: ----- Method: Cogit>>mapObjectReferencesInMachineCodeForFullGC (in category 'garbage collection') ----- mapObjectReferencesInMachineCodeForFullGC "Update all references to objects in machine code for a full gc. Since the current (New)ObjectMemory GC makes everything old in a full GC a method not referring to young will not refer to young afterwards" + | cogMethod writableCogMethod | - | cogMethod | - <var: #cogMethod type: #'CogMethod *'> codeModified := false. self mapObjectReferencesInGeneratedRuntime. cogMethod := self cCoerceSimple: methodZoneBase to: #'CogMethod *'. [cogMethod < methodZone limitZony] whileTrue: [cogMethod cmType ~= CMFree ifTrue: [self assert: (self cogMethodDoesntLookKosher: cogMethod) = 0. + writableCogMethod := self writableMethodFor: cogMethod. + writableCogMethod selector: (objectRepresentation remapOop: cogMethod selector). - cogMethod selector: (objectRepresentation remapOop: cogMethod selector). cogMethod cmType = CMClosedPIC ifTrue: [self assert: cogMethod cmRefersToYoung not. self mapObjectReferencesInClosedPIC: cogMethod] ifFalse: [cogMethod cmType = CMMethod ifTrue: [self assert: cogMethod objectHeader = objectMemory nullHeaderForMachineCodeMethod. + writableCogMethod methodObject: (objectRepresentation remapOop: cogMethod methodObject)]. - cogMethod methodObject: (objectRepresentation remapOop: cogMethod methodObject)]. self mapFor: cogMethod performUntil: #remapIfObjectRef:pc:hasYoung: arg: 0. (cogMethod cmRefersToYoung and: [objectRepresentation allYoungObjectsAgeInFullGC]) ifTrue: + [writableCogMethod cmRefersToYoung: false]]]. - [cogMethod cmRefersToYoung: false]]]. cogMethod := methodZone methodAfter: cogMethod]. methodZone pruneYoungReferrers. codeModified ifTrue: "After updating oops in inline caches we need to flush the icache." [backEnd flushICacheFrom: codeBase asUnsignedInteger to: methodZone limitZony asUnsignedInteger]! Item was changed: ----- Method: Cogit>>mapObjectReferencesInMachineCodeForYoungGC (in category 'garbage collection') ----- mapObjectReferencesInMachineCodeForYoungGC "Update all references to objects in machine code for either a Spur scavenging gc or a Squeak V3 incremental GC. Avoid scanning all code by using the youngReferrers list. In a young gc a method referring to young may no longer refer to young, but a method not referring to young cannot and will not refer to young afterwards." | pointer cogMethod hasYoungObj hasYoungObjPtr | - <var: #cogMethod type: #'CogMethod *'> hasYoungObj := false. hasYoungObjPtr := (self addressOf: hasYoungObj put: [:val| hasYoungObj := val]) asInteger. codeModified := false. pointer := methodZone youngReferrers. [pointer < methodZone zoneEnd] whileTrue: [self assert: hasYoungObj not. cogMethod := coInterpreter cCoerceSimple: (objectMemory longAt: pointer) to: #'CogMethod *'. cogMethod cmType = CMFree ifTrue: [self assert: cogMethod cmRefersToYoung not] ifFalse: [self assert: (self cogMethodDoesntLookKosher: cogMethod) = 0. cogMethod cmRefersToYoung ifTrue: + [| writableCogMethod | - [| writableVersion | self assert: (cogMethod cmType = CMMethod or: [cogMethod cmType = CMOpenPIC]). + writableCogMethod := self writableMethodFor: cogMethod. + writableCogMethod selector: (objectRepresentation remapOop: cogMethod selector). - writableVersion := self writableMethodFor: cogMethod. - writableVersion selector: (objectRepresentation remapOop: cogMethod selector). (objectMemory isYoung: cogMethod selector) ifTrue: [hasYoungObj := true]. cogMethod cmType = CMMethod ifTrue: [self assert: cogMethod objectHeader = objectMemory nullHeaderForMachineCodeMethod. + writableCogMethod methodObject: (objectRepresentation remapOop: cogMethod methodObject). - writableVersion methodObject: (objectRepresentation remapOop: cogMethod methodObject). (objectMemory isYoung: cogMethod methodObject) ifTrue: [hasYoungObj := true]]. self mapFor: cogMethod performUntil: #remapIfObjectRef:pc:hasYoung: arg: hasYoungObjPtr. hasYoungObj ifTrue: [hasYoungObj := false] + ifFalse: [writableCogMethod cmRefersToYoung: false]]]. - ifFalse: [writableVersion cmRefersToYoung: false]]]. pointer := pointer + objectMemory wordSize]. methodZone pruneYoungReferrers. codeModified ifTrue: "After updating oops in inline caches we need to flush the icache." [backEnd flushICacheFrom: methodZoneBase asUnsignedInteger to: methodZone limitZony asUnsignedInteger]! Item was changed: ----- Method: Cogit>>printCogMethodFor: (in category 'printing') ----- printCogMethodFor: address <api> <var: #address type: #'void *'> + (methodZone methodFor: address) + ifNil: [(self codeEntryFor: address) - | cogMethod | - <var: #cogMethod type: #'CogMethod *'> - cogMethod := methodZone methodFor: address. - cogMethod = 0 - ifTrue: [(self codeEntryFor: address) ifNil: [coInterpreter print: 'not a method'; cr] ifNotNil: [coInterpreter print: 'trampoline '; print: (self codeEntryNameFor: address); cr]] + ifNotNil: [:cogMethod| coInterpreter printCogMethod: cogMethod]! - ifFalse: [coInterpreter printCogMethod: cogMethod]! Item was changed: ----- Method: Cogit>>printCogMethodHeaderFor: (in category 'printing') ----- printCogMethodHeaderFor: address <doNotGenerate> + (methodZone methodFor: address) + ifNil: [coInterpreter print: 'not a method'; cr] + ifNotNil: [:cogMethod| self printMethodHeader: cogMethod on: coInterpreter transcript]! - | cogMethod | - <var: #cogMethod type: #'CogMethod *'> - cogMethod := methodZone methodFor: address. - cogMethod = 0 - ifTrue: [coInterpreter print: 'not a method'; cr] - ifFalse: [self printMethodHeader: cogMethod on: coInterpreter transcript]! Item was changed: ----- Method: InLineLiteralsManager>>storeLiteral:atAnnotatedAddress:using: (in category 'garbage collection') ----- storeLiteral: literal atAnnotatedAddress: address using: instruction "Normally literals are embedded in instructions and the annotation is at the start of the following instruction, to cope with literals embedded in variable-length instructions, since, e.g. on x86, the literal typically comes at the end of the instruction." <var: 'address' type: #usqInt> <var: 'instruction' type: #'AbstractInstruction *'> + <inline: #always> - <inline: true> ^instruction storeLiteral: literal beforeFollowingAddress: address! Item was changed: ----- Method: OutOfLineLiteralsManager>>storeLiteral:atAnnotatedAddress:using: (in category 'garbage collection') ----- storeLiteral: literal atAnnotatedAddress: address using: instruction "With out-of-line literals, the IsObjectReference annotation refers to the start of the literal and hence access the memory directly." <var: 'address' type: #usqInt> <var: 'instruction' type: #'AbstractInstruction *'> + <inline: #always> + cogit codeLongAt: address put: literal! - <inline: true> - objectMemory longAt: address put: literal! |
Free forum by Nabble | Edit this page |