Skip to content

Commit 6004f99

Browse files
committed
Pushing up profiling data methods to SimpleStackCogit
1 parent ddc9647 commit 6004f99

File tree

2 files changed

+178
-178
lines changed

2 files changed

+178
-178
lines changed

smalltalksrc/VMMaker/SimpleStackBasedCogit.class.st

Lines changed: 177 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -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' }
30173047
SimpleStackBasedCogit >> 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' }
30753251
SimpleStackBasedCogit >> putSelfInReceiverResultReg [
30763252
<inline: true>

smalltalksrc/VMMaker/StackToRegisterMappingCogit.class.st

Lines changed: 1 addition & 177 deletions
Original file line numberDiff line numberDiff line change
@@ -136,8 +136,7 @@ Class {
136136
'realCECallCogCodePopReceiverArg0Regs',
137137
'realCECallCogCodePopReceiverArg1Arg0Regs',
138138
'deadCode',
139-
'useTwoPaths',
140-
'counterIndex'
139+
'useTwoPaths'
141140
],
142141
#pools : [
143142
'CogCompilationConstants',
@@ -3729,35 +3728,6 @@ StackToRegisterMappingCogit >> picMissTrampolines [
37293728

37303729
]
37313730

3732-
{ #category : 'method introspection' }
3733-
StackToRegisterMappingCogit >> populate: tuple withPICInfoFor: cPIC firstCacheTag: firstCacheTag [
3734-
"Populate tuple (which must be large enough) with the ClosedPIC's target method class pairs.
3735-
The first entry in tuple contains the bytecode pc for the send, so skip the tuple's first field."
3736-
<var: #cPIC type: #'CogMethod *'>
3737-
| picCaseMachineCodePC cacheTag classOop entryPoint targetMethod value |
3738-
<var: #targetMethod type: #'CogMethod *'>
3739-
3740-
1 to: cPIC cPICNumCases do: [:i|
3741-
picCaseMachineCodePC := self addressOfEndOfCase: i inCPIC: cPIC.
3742-
cacheTag := i = 1
3743-
ifTrue: [firstCacheTag]
3744-
ifFalse: [backEnd literalBeforeFollowingAddress: picCaseMachineCodePC - backEnd jumpLongConditionalByteSize].
3745-
3746-
classOop := objectRepresentation classForInlineCacheTag: cacheTag.
3747-
objectMemory storePointer: i * 2 - 1 ofObject: tuple withValue: classOop.
3748-
entryPoint := i = 1
3749-
ifTrue: [backEnd jumpLongTargetBeforeFollowingAddress: picCaseMachineCodePC]
3750-
ifFalse: [backEnd jumpLongConditionalTargetBeforeFollowingAddress: picCaseMachineCodePC].
3751-
"Find target from jump. A jump to the MNU entry-point should collect #doesNotUnderstand:"
3752-
(cPIC containsAddress: entryPoint)
3753-
ifTrue: [ value := objectMemory splObj: SelectorDoesNotUnderstand ]
3754-
ifFalse: [
3755-
targetMethod := self cCoerceSimple: entryPoint - cmNoCheckEntryOffset to: #'CogMethod *'.
3756-
self assert: targetMethod cmType = CMMethod.
3757-
value := targetMethod methodObject ].
3758-
objectMemory storePointer: i * 2 ofObject: tuple withValue: value ]
3759-
]
3760-
37613731
{ #category : 'testing' }
37623732
StackToRegisterMappingCogit >> prevInstIsPCAnnotated [
37633733
| prevIndex prevInst |
@@ -3861,152 +3831,6 @@ StackToRegisterMappingCogit >> printSimStack: aSimStack toDepth: limit spillBase
38613831
flush ]
38623832
]
38633833

3864-
{ #category : 'method introspection' }
3865-
StackToRegisterMappingCogit >> profilingDataFor: descriptor Annotation: isBackwardBranchAndAnnotation Mcpc: mcpc Bcpc: bcpc Method: cogMethodArg [
3866-
<var: #descriptor type: #'BytecodeDescriptor *'>
3867-
<var: #mcpc type: #'char *'>
3868-
<var: #cogMethodArg type: #'void *'>
3869-
<var: #methodClassIfSuper type: #'sqInt'>
3870-
| annotation entryPoint tuple counter |
3871-
"N.B. Counters are always 32-bits, having two 16-bit halves for the reached and taken counts."
3872-
<var: #counter type: #'unsigned int'>
3873-
3874-
descriptor ifNil:
3875-
[^0].
3876-
descriptor isBranch ifTrue:
3877-
["it's a branch; conditional?"
3878-
(descriptor isBranchTrue or: [descriptor isBranchFalse]) ifTrue: [ | counters |
3879-
counters := self
3880-
cCoerce: ((self
3881-
cCoerceSimple: cogMethodArg
3882-
to: #'CogMethod *') counters)
3883-
to: #'usqInt *'.
3884-
"If no counters are available, do not record counters"
3885-
counters = 0 ifTrue: [ ^ 0 ].
3886-
3887-
counter := counters at: counterIndex.
3888-
tuple := self profilingDataForCounter: counter at: bcpc + 1.
3889-
tuple = 0 ifTrue: [^PrimErrNoMemory].
3890-
objectMemory
3891-
storePointer: introspectionDataIndex
3892-
ofObject: introspectionData
3893-
withValue: tuple.
3894-
introspectionDataIndex := introspectionDataIndex + 1.
3895-
counterIndex := counterIndex + 1].
3896-
^0].
3897-
3898-
annotation := isBackwardBranchAndAnnotation >> 1.
3899-
((self isPureSendAnnotation: annotation)
3900-
and: [entryPoint := backEnd callTargetFromReturnAddress: mcpc asUnsignedInteger.
3901-
entryPoint > methodZoneBase]) ifFalse: "send is not linked, or is not a send"
3902-
[^0].
3903-
3904-
"It's a linked send; find which kind."
3905-
self targetMethodAndSendTableFor: entryPoint
3906-
annotation: annotation
3907-
into: [:targetCogCode :sendTable| | methodClassIfSuper association |
3908-
methodClassIfSuper := nil.
3909-
sendTable = superSendTrampolines ifTrue: [
3910-
methodClassIfSuper := coInterpreter methodClassOf: (self cCoerceSimple: cogMethodArg to: #'CogMethod *') methodObject.
3911-
].
3912-
sendTable = directedSuperSendTrampolines ifTrue: [
3913-
association := backEnd literalBeforeInlineCacheTagAt: mcpc asUnsignedInteger.
3914-
methodClassIfSuper := objectRepresentation valueOfAssociation: association ].
3915-
tuple := self profilingDataForSendTo: targetCogCode
3916-
methodClassIfSuper: methodClassIfSuper
3917-
at: mcpc
3918-
bcpc: bcpc + 1].
3919-
3920-
tuple = 0 ifTrue: [^PrimErrNoMemory].
3921-
objectMemory
3922-
storePointer: introspectionDataIndex
3923-
ofObject: introspectionData
3924-
withValue: tuple.
3925-
introspectionDataIndex := introspectionDataIndex + 1.
3926-
^0
3927-
]
3928-
3929-
{ #category : 'method introspection' }
3930-
StackToRegisterMappingCogit >> profilingDataFor: cogMethod into: arrayObj [
3931-
3932-
"Collect the branch and send data for cogMethod, storing it into arrayObj."
3933-
3934-
<api>
3935-
<var: #cogMethod type: #'CogMethod *'>
3936-
| errCode |
3937-
"If the method is frameless, it has no message sends. No need to continue."
3938-
cogMethod stackCheckOffset = 0 ifTrue: [ ^ 0 ].
3939-
3940-
introspectionDataIndex := counterIndex := 0.
3941-
introspectionData := arrayObj.
3942-
errCode := self
3943-
mapFor: (self cCoerceSimple: cogMethod to: #'CogMethod *')
3944-
bcpc: (coInterpreter startPCOfMethod: cogMethod methodObject)
3945-
performUntil: #profilingDataFor:Annotation:Mcpc:Bcpc:Method:
3946-
arg: cogMethod asVoidPointer.
3947-
errCode ~= 0 ifTrue: [
3948-
self assert: errCode = PrimErrNoMemory.
3949-
^ -1 ].
3950-
^ introspectionDataIndex
3951-
]
3952-
3953-
{ #category : 'method introspection' }
3954-
StackToRegisterMappingCogit >> profilingDataForCounter: counter at: bcpc [
3955-
"Undefined by now, do nothing"
3956-
3957-
^ 0
3958-
]
3959-
3960-
{ #category : 'method introspection' }
3961-
StackToRegisterMappingCogit >> profilingDataForSendTo: cogCodeSendTarget methodClassIfSuper: methodClassOrNil at: sendMcpc bcpc: sendBcpc [
3962-
"Answer a tuple with the send data for a linked send to cogMethod.
3963-
If the target is a CogMethod (monomorphic send) answer
3964-
{ bytecode pc, inline cache class, target method }
3965-
If the target is an open PIC (megamorphic send) answer
3966-
{ bytecode pc, nil, send selector }
3967-
If the target is a closed PIC (polymorphic send) answer
3968-
{ bytecode pc, first class, target method, second class, second target method, ... }"
3969-
<var: #cogCodeSendTarget type: #'CogMethod *'>
3970-
<var: #sendMcpc type: #'char *'>
3971-
| tuple class |
3972-
tuple := objectMemory
3973-
eeInstantiateClassIndex: ClassArrayCompactIndex
3974-
format: objectMemory arrayFormat
3975-
numSlots: (cogCodeSendTarget cmType = CMPolymorphicIC
3976-
ifTrue: [2 * cogCodeSendTarget cPICNumCases + 1]
3977-
ifFalse: [3]).
3978-
tuple = 0 ifTrue:
3979-
[^0].
3980-
3981-
objectMemory storePointerUnchecked: 0 ofObject: tuple withValue: (objectMemory integerObjectOf: sendBcpc).
3982-
3983-
"Monomorphic - linked against a single method"
3984-
cogCodeSendTarget cmType = CMMethod ifTrue: [
3985-
"If it is not a super send, we don't have a class, let's extract it from the call site"
3986-
class := methodClassOrNil ifNil: [
3987-
objectRepresentation classForInlineCacheTag: (backEnd inlineCacheTagAt: sendMcpc asUnsignedInteger)].
3988-
objectMemory
3989-
storePointer: 1 ofObject: tuple withValue: class;
3990-
storePointer: 2 ofObject: tuple withValue: cogCodeSendTarget methodObject.
3991-
^tuple ].
3992-
3993-
cogCodeSendTarget cmType = CMPolymorphicIC ifTrue: [
3994-
self
3995-
populate: tuple
3996-
withPICInfoFor: cogCodeSendTarget
3997-
firstCacheTag: (backEnd inlineCacheTagAt: sendMcpc asUnsignedInteger).
3998-
^tuple ].
3999-
4000-
cogCodeSendTarget cmType = CMMegamorphicIC ifTrue: [
4001-
objectMemory
4002-
storePointerUnchecked: 1 ofObject: tuple withValue: objectMemory nilObject;
4003-
storePointer: 2 ofObject: tuple withValue: cogCodeSendTarget selector.
4004-
^tuple ].
4005-
4006-
self error: 'invalid method type'.
4007-
^0 "to get Slang to type this method as answering sqInt"
4008-
]
4009-
40103834
{ #category : 'span functions' }
40113835
StackToRegisterMappingCogit >> pushNilSize: aMethodObj numInitialNils: numInitialNils [
40123836
<inline: true>

0 commit comments

Comments
 (0)