@@ -12,7 +12,8 @@ Class {
1212 ' externalPrimJumpOffsets' ,
1313 ' externalSetPrimOffsets' ,
1414 ' introspectionDataIndex' ,
15- ' introspectionData'
15+ ' introspectionData' ,
16+ ' counterIndex'
1617 ],
1718 #pools : [
1819 ' VMClassIndices' ,
@@ -3009,6 +3010,35 @@ SimpleStackBasedCogit >> picAbortTrampolineFor: numArgs [
30093010 ^ cePICAbortTrampoline
30103011]
30113012
3013+ { #category : ' method introspection' }
3014+ SimpleStackBasedCogit >> populate: tuple withPICInfoFor: cPIC firstCacheTag: firstCacheTag [
3015+ " Populate tuple (which must be large enough) with the ClosedPIC's target method class pairs.
3016+ The first entry in tuple contains the bytecode pc for the send, so skip the tuple's first field."
3017+ < var: #cPIC type: #' CogMethod *' >
3018+ | picCaseMachineCodePC cacheTag classOop entryPoint targetMethod value |
3019+ < var: #targetMethod type: #' CogMethod *' >
3020+
3021+ 1 to: cPIC cPICNumCases do: [:i |
3022+ picCaseMachineCodePC := self addressOfEndOfCase: i inCPIC: cPIC.
3023+ cacheTag := i = 1
3024+ ifTrue: [firstCacheTag]
3025+ ifFalse: [backEnd literal32BeforeFollowingAddress: picCaseMachineCodePC - backEnd jumpLongConditionalByteSize].
3026+
3027+ classOop := objectRepresentation classForInlineCacheTag: cacheTag.
3028+ objectMemory storePointer: i * 2 - 1 ofObject: tuple withValue: classOop.
3029+ entryPoint := i = 1
3030+ ifTrue: [backEnd jumpLongTargetBeforeFollowingAddress: picCaseMachineCodePC]
3031+ ifFalse: [backEnd jumpLongConditionalTargetBeforeFollowingAddress: picCaseMachineCodePC].
3032+ " Find target from jump. A jump to the MNU entry-point should collect #doesNotUnderstand:"
3033+ (cPIC containsAddress: entryPoint)
3034+ ifTrue: [ value := objectMemory splObj: SelectorDoesNotUnderstand ]
3035+ ifFalse: [
3036+ targetMethod := self cCoerceSimple: entryPoint - cmNoCheckEntryOffset to: #' CogMethod *' .
3037+ self assert: targetMethod cmType = CMMethod .
3038+ value := targetMethod methodObject ].
3039+ objectMemory storePointer: i * 2 ofObject: tuple withValue: value ]
3040+ ]
3041+
30123042{ #category : ' primitive generators' }
30133043SimpleStackBasedCogit >> primitiveDescriptor [
30143044 " If there is a generator for the current primitive then answer it;
@@ -3067,6 +3097,152 @@ SimpleStackBasedCogit >> primitivePropertyFlags: primIndex primitiveDescriptor:
30673097 ^ baseFlags
30683098]
30693099
3100+ { #category : ' method introspection' }
3101+ SimpleStackBasedCogit >> profilingDataFor: descriptor Annotation: isBackwardBranchAndAnnotation Mcpc: mcpc Bcpc: bcpc Method: cogMethodArg [
3102+ < var: #descriptor type: #' BytecodeDescriptor *' >
3103+ < var: #mcpc type: #' char *' >
3104+ < var: #cogMethodArg type: #' void *' >
3105+ < var: #methodClassIfSuper type: #' sqInt' >
3106+ | annotation entryPoint tuple counter |
3107+ " N.B. Counters are always 32-bits, having two 16-bit halves for the reached and taken counts."
3108+ < var: #counter type: #' unsigned int' >
3109+
3110+ descriptor ifNil:
3111+ [^ 0 ].
3112+ descriptor isBranch ifTrue:
3113+ [" it's a branch; conditional?"
3114+ (descriptor isBranchTrue or : [descriptor isBranchFalse]) ifTrue: [ | counters |
3115+ counters := self
3116+ cCoerce: ((self
3117+ cCoerceSimple: cogMethodArg
3118+ to: #' CogMethod *' ) counters)
3119+ to: #' usqInt *' .
3120+ " If no counters are available, do not record counters"
3121+ counters = 0 ifTrue: [ ^ 0 ].
3122+
3123+ counter := counters at: counterIndex.
3124+ tuple := self profilingDataForCounter: counter at: bcpc + 1 .
3125+ tuple = 0 ifTrue: [^ PrimErrNoMemory ].
3126+ objectMemory
3127+ storePointer: introspectionDataIndex
3128+ ofObject: introspectionData
3129+ withValue: tuple.
3130+ introspectionDataIndex := introspectionDataIndex + 1 .
3131+ counterIndex := counterIndex + 1 ].
3132+ ^ 0 ].
3133+
3134+ annotation := isBackwardBranchAndAnnotation >> 1 .
3135+ ((self isPureSendAnnotation: annotation)
3136+ and : [entryPoint := backEnd callTargetFromReturnAddress: mcpc asUnsignedInteger.
3137+ entryPoint > methodZoneBase]) ifFalse: " send is not linked, or is not a send"
3138+ [^ 0 ].
3139+
3140+ " It's a linked send; find which kind."
3141+ self targetMethodAndSendTableFor: entryPoint
3142+ annotation: annotation
3143+ into: [:targetCogCode :sendTable | | methodClassIfSuper association |
3144+ methodClassIfSuper := nil .
3145+ sendTable = superSendTrampolines ifTrue: [
3146+ methodClassIfSuper := coInterpreter methodClassOf: (self cCoerceSimple: cogMethodArg to: #' CogMethod *' ) methodObject.
3147+ ].
3148+ sendTable = directedSuperSendTrampolines ifTrue: [
3149+ association := backEnd literalBeforeInlineCacheTagAt: mcpc asUnsignedInteger.
3150+ methodClassIfSuper := objectRepresentation valueOfAssociation: association ].
3151+ tuple := self profilingDataForSendTo: targetCogCode
3152+ methodClassIfSuper: methodClassIfSuper
3153+ at: mcpc
3154+ bcpc: bcpc + 1 ].
3155+
3156+ tuple = 0 ifTrue: [^ PrimErrNoMemory ].
3157+ objectMemory
3158+ storePointer: introspectionDataIndex
3159+ ofObject: introspectionData
3160+ withValue: tuple.
3161+ introspectionDataIndex := introspectionDataIndex + 1 .
3162+ ^ 0
3163+ ]
3164+
3165+ { #category : ' method introspection' }
3166+ SimpleStackBasedCogit >> profilingDataFor: cogMethod into: arrayObj [
3167+
3168+ " Collect the branch and send data for cogMethod, storing it into arrayObj."
3169+
3170+ < api>
3171+ < var: #cogMethod type: #' CogMethod *' >
3172+ | errCode |
3173+ " If the method is frameless, it has no message sends. No need to continue."
3174+ cogMethod stackCheckOffset = 0 ifTrue: [ ^ 0 ].
3175+
3176+ introspectionDataIndex := counterIndex := 0 .
3177+ introspectionData := arrayObj.
3178+ errCode := self
3179+ mapFor: (self cCoerceSimple: cogMethod to: #' CogMethod *' )
3180+ bcpc: (coInterpreter startPCOfMethod: cogMethod methodObject)
3181+ performUntil: #profilingDataFor:Annotation:Mcpc:Bcpc:Method:
3182+ arg: cogMethod asVoidPointer.
3183+ errCode ~= 0 ifTrue: [
3184+ self assert: errCode = PrimErrNoMemory .
3185+ ^ - 1 ].
3186+ ^ introspectionDataIndex
3187+ ]
3188+
3189+ { #category : ' method introspection' }
3190+ SimpleStackBasedCogit >> profilingDataForCounter: counter at: bcpc [
3191+ " Undefined by now, do nothing"
3192+
3193+ ^ 0
3194+ ]
3195+
3196+ { #category : ' method introspection' }
3197+ SimpleStackBasedCogit >> profilingDataForSendTo: cogCodeSendTarget methodClassIfSuper: methodClassOrNil at: sendMcpc bcpc: sendBcpc [
3198+ " Answer a tuple with the send data for a linked send to cogMethod.
3199+ If the target is a CogMethod (monomorphic send) answer
3200+ { bytecode pc, inline cache class, target method }
3201+ If the target is an open PIC (megamorphic send) answer
3202+ { bytecode pc, nil, send selector }
3203+ If the target is a closed PIC (polymorphic send) answer
3204+ { bytecode pc, first class, target method, second class, second target method, ... }"
3205+ < var: #cogCodeSendTarget type: #' CogMethod *' >
3206+ < var: #sendMcpc type: #' char *' >
3207+ | tuple class |
3208+ tuple := objectMemory
3209+ eeInstantiateClassIndex: ClassArrayCompactIndex
3210+ format: objectMemory arrayFormat
3211+ numSlots: (cogCodeSendTarget cmType = CMPolymorphicIC
3212+ ifTrue: [2 * cogCodeSendTarget cPICNumCases + 1 ]
3213+ ifFalse: [3 ]).
3214+ tuple = 0 ifTrue:
3215+ [^ 0 ].
3216+
3217+ objectMemory storePointerUnchecked: 0 ofObject: tuple withValue: (objectMemory integerObjectOf: sendBcpc).
3218+
3219+ " Monomorphic - linked against a single method"
3220+ cogCodeSendTarget cmType = CMMethod ifTrue: [
3221+ " If it is not a super send, we don't have a class, let's extract it from the call site"
3222+ class := methodClassOrNil ifNil: [
3223+ objectRepresentation classForInlineCacheTag: (backEnd inlineCacheTagAt: sendMcpc asUnsignedInteger)].
3224+ objectMemory
3225+ storePointer: 1 ofObject: tuple withValue: class ;
3226+ storePointer: 2 ofObject: tuple withValue: cogCodeSendTarget methodObject.
3227+ ^ tuple ].
3228+
3229+ cogCodeSendTarget cmType = CMPolymorphicIC ifTrue: [
3230+ self
3231+ populate: tuple
3232+ withPICInfoFor: cogCodeSendTarget
3233+ firstCacheTag: (backEnd inlineCacheTagAt: sendMcpc asUnsignedInteger).
3234+ ^ tuple ].
3235+
3236+ cogCodeSendTarget cmType = CMMegamorphicIC ifTrue: [
3237+ objectMemory
3238+ storePointerUnchecked: 1 ofObject: tuple withValue: objectMemory nilObject;
3239+ storePointer: 2 ofObject: tuple withValue: cogCodeSendTarget selector.
3240+ ^ tuple ].
3241+
3242+ self error: ' invalid method type' .
3243+ ^ 0 " to get Slang to type this method as answering sqInt"
3244+ ]
3245+
30703246{ #category : ' bytecode generator support' }
30713247SimpleStackBasedCogit >> putSelfInReceiverResultReg [
30723248 < inline: true >
0 commit comments