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