VM Maker: VMMaker.oscog-eem.2401.mcz

Previous Topic Next Topic
 
classic Classic list List threaded Threaded
1 message Options
Reply | Threaded
Open this post in threaded view
|

VM Maker: VMMaker.oscog-eem.2401.mcz

commits-2
 
Eliot Miranda uploaded a new version of VMMaker to project VM Maker:
http://source.squeak.org/VMMaker/VMMaker.oscog-eem.2401.mcz

==================== Summary ====================

Name: VMMaker.oscog-eem.2401
Author: eem
Time: 1 June 2018, 3:09:07.535061 pm
UUID: 29232e0e-c9e3-41d8-ae75-519db862e02c
Ancestors: VMMaker.oscog-eem.2400

Cogit: Answer better closed PIC data from primitiveCollectCogCodeConstituents.  i.e. scan preceding methods for references to closed PICs and store temporarily the send site's first case cache tag (mapped to a class) in the PIC's methodObject field for later harvesting.  Answder am array of PIC selector followed by class, target pairs, where target is either a method or #doesNotUnderstand:.

Slang:
Avoid issuing warnings for <var: 'foo' declareC: 'extern someFunction()'> pragmas.
Extract type info from extern declarations as well as static declarations.

=============== Diff against VMMaker.oscog-eem.2400 ===============

Item was changed:
  ----- Method: CCodeGenerator>>extractTypeFor:fromDeclaration: (in category 'utilities') -----
  extractTypeFor: aVariable fromDeclaration: aVariableDeclaration
  "Eliminate inessentials from aVariableDeclaration to answer a C type without the variable,
  or initializations etc"
  | decl |
+ ((aVariableDeclaration beginsWith: 'static ')
+ or: [aVariableDeclaration beginsWith: 'extern ']) ifTrue:
+ [^self extractTypeFor: aVariable fromDeclaration: (aVariableDeclaration allButFirst: 7)].
+ decl := (aVariableDeclaration indexOf: $= ifAbsent: [])
+ ifNotNil: [:index| aVariableDeclaration copyFrom: 1 to: index - 1]
+ ifNil: [aVariableDeclaration].
- decl := aVariableDeclaration.
- (decl beginsWith: 'static') ifTrue:
- [decl := decl allButFirst: 6].
- (decl indexOf: $= ifAbsent: []) ifNotNil:
- [:index| decl := decl copyFrom: 1 to: index - 1].
  decl := decl copyReplaceAll: aVariable with: '' tokenish: [:ch| ch = $_ or: [ch isAlphaNumeric]].
  ^self baseTypeForType: decl!

Item was added:
+ ----- Method: CCodeGenerator>>isFunctionalCType: (in category 'type inference') -----
+ isFunctionalCType: aType
+ "Answer if aType is either a function or a pointer to a function."
+ ^aType last == $) and: [(aType indexOf: $() > 0]!

Item was changed:
  ----- Method: CogVMSimulator>>utilitiesMenu: (in category 'UI') -----
  utilitiesMenu: aMenuMorph
  aMenuMorph
  add: 'toggle transcript' action: #toggleTranscript;
  add: 'clone VM' action: #cloneSimulationWindow;
  addLine;
  add: 'print ext head frame' action: #printExternalHeadFrame;
  add: 'print int head frame' action: #printHeadFrame;
  add: 'print mc/cog head frame' action: [self printFrame: cogit processor fp WithSP: cogit processor sp];
  add: 'short print ext head frame & callers' action: [self shortPrintFrameAndCallers: framePointer];
  add: 'short print int head frame & callers' action: [self shortPrintFrameAndCallers: localFP];
  add: 'short print mc/cog head frame & callers' action: [self shortPrintFrameAndCallers: cogit processor fp];
  add: 'long print ext head frame & callers' action: [self printFrameAndCallers: framePointer SP: stackPointer];
  add: 'long print int head frame & callers' action: [self printFrameAndCallers: localFP SP: localSP];
  add: 'long print mc/cog head frame & callers' action: [self printFrameAndCallers: cogit processor fp SP: cogit processor sp];
  add: 'print frame...' action: [(self promptHex: 'print frame') ifNotNil: [:fp| self printFrame: fp]];
  add: 'print call stack' action: #printCallStack;
  add: 'print stack call stack' action: #printStackCallStack;
  add: 'print stack call stack of...' action: [(self promptHex: 'frame') ifNotNil: [:fp| self printStackCallStackOf: fp]];
  add: 'print call stack of...' action: [(self promptHex: 'context or process oop') ifNotNil: [:obj| self printCallStackOf: obj]];
  add: 'print call stack of frame...' action: [(self promptHex: 'frame') ifNotNil: [:fp| self printCallStackFP: fp]];
  add: 'print all stacks' action: #printAllStacks;
  add: 'write back local ptrs' action: [stackPointer := localSP. framePointer := localFP. instructionPointer := localIP.
  self writeBackHeadFramePointers];
  add: 'write back mc ptrs' action: [stackPointer := cogit processor sp. framePointer := cogit processor fp. instructionPointer := cogit processor pc.
  self externalWriteBackHeadFramePointers];
  addLine;
  add: 'print rump C stack' action: [objectMemory printMemoryFrom: cogit processor sp to: cogit getCStackPointer];
  add: 'print registers' action: [cogit processor printRegistersOn: transcript];
  add: 'print register map' action: [cogit printRegisterMapOn: transcript];
  add: 'disassemble method/trampoline...' action: [(self promptHex: 'pc') ifNotNil: [:pc| cogit disassembleCodeAt: pc]];
  add: 'disassemble method/trampoline at pc' action:
  [cogit disassembleCodeAt: (((cogit codeEntryFor: cogit processor pc) isNil
   and: [(cogit methodZone methodFor: cogit processor pc) = 0])
  ifTrue: [instructionPointer]
  ifFalse: [cogit processor pc])];
  add: 'disassemble ext head frame method' action: [cogit disassembleMethod: (self frameMethod: framePointer)];
  add: 'print oop...' action: [(self promptHex: 'print oop') ifNotNil: [:oop| self printOop: oop]];
  add: 'long print oop...' action: [(self promptHex: 'print oop') ifNotNil: [:oop| self longPrintOop: oop]];
  add: 'print context...' action: [(self promptHex: 'print context') ifNotNil: [:oop| self printContext: oop]];
  add: 'symbolic method...' action: [(self promptHex: 'method bytecodes') ifNotNil: [:oop| self symbolicMethod: oop]];
  addLine;
  add: 'inspect object memory' target: objectMemory action: #inspect;
  add: 'run leak checker' action: [Cursor execute showWhile: [self runLeakChecker]];
  add: 'inspect cointerpreter' action: #inspect;
  add: 'inspect cogit' target: cogit action: #inspect;
  add: 'inspect method zone' target: cogit methodZone action: #inspect.
  self isThreadedVM ifTrue:
  [aMenuMorph add: 'inspect thread manager' target: self threadManager action: #inspect].
  aMenuMorph
  addLine;
  add: 'print cog methods' target: cogMethodZone action: #printCogMethods;
+ add: 'print cog methods with prim...' action:
+ [(self promptNum: 'prim index') ifNotNil: [:pix| cogMethodZone printCogMethodsWithPrimitive: pix]];
- add: 'print cog methods with prim...' action: [(self promptNum: 'prim index') ifNotNil: [:pix| cogMethodZone printCogMethodsWithPrimitive: pix]];
  add: 'print cog methods with selector...' action:
  [|s| s := UIManager default request: 'selector'.
  s notEmpty ifTrue:
  [s = 'nil' ifTrue: [s := nil].
  cogMethodZone methodsDo:
  [:m|
  (s ifNil: [m selector = objectMemory nilObject]
  ifNotNil: [(objectMemory numBytesOf: m selector) = s size
  and: [(self str: s
  n: (m selector + objectMemory baseHeaderSize)
  cmp: (objectMemory numBytesOf: m selector)) = 0]]) ifTrue:
  [cogit printCogMethod: m]]]];
  add: 'print cog methods with method...' action:
+ [(self promptHex: 'method') ifNotNil: [:methodOop| cogMethodZone printCogMethodsWithMethod: methodOop]];
- [(self promptHex: 'method') ifNotNil: [:methodOop|
- cogMethodZone methodsDo:
- [:m|
- m methodObject = methodOop ifTrue:
- [cogit printCogMethod: m]]]];
  add: 'print cog method for...' action: [(self promptHex: 'pc') ifNotNil: [:pc| cogit printCogMethodFor: pc]];
  add: 'print cog method header for...' action: [(self promptHex: 'pc') ifNotNil: [:pc| cogit printCogMethodHeaderFor: pc]];
  add: 'print trampoline table' target: cogit action: #printTrampolineTable;
  add: 'print prim trace log' action: #dumpPrimTraceLog;
  add: 'report recent instructions' target: cogit action: #reportLastNInstructions;
  add: (cogit printRegisters
  ifTrue: ['no print registers each instruction']
  ifFalse: ['print registers each instruction'])
  action: [cogit printRegisters: cogit printRegisters not];
  add: (cogit printInstructions
  ifTrue: ['no print instructions each instruction']
  ifFalse: ['print instructions each instruction'])
  action: [cogit printInstructions: cogit printInstructions not];
  addLine;
  add: (cogit singleStep
  ifTrue: ['no single step']
  ifFalse: ['single step'])
  action: [cogit singleStep: cogit singleStep not];
  add: 'click step' action: [cogit setClickStepBreakBlock];
  add: 'set break pc', cogit breakPC menuPrompt, '...-ve to disable or remove' action: [cogit promptForBreakPC];
  add: 'set break count...' action: [|s| s := UIManager default request: 'break count (dec)'.
  s notEmpty ifTrue: [breakCount := Integer readFrom: s readStream]];
  add: 'set break selector...' action: [|s| s := UIManager default request: 'break selector (MNU:foo for MNU)'.
  s notEmpty ifTrue:
  [(s size > 4 and: [s beginsWith: 'MNU:'])
  ifTrue: [self setBreakMNUSelector: (s allButFirst: 4)]
  ifFalse: [self setBreakSelector: s]]];
  add: 'set break block...' action: [|s| s := UIManager default request: 'break block' initialAnswer: '[:theCogit| false]'.
  s notEmpty ifTrue: [self setBreakBlockFromString: s]];
  add: 'set cogit break method...' action: [(self promptHex: 'cogit breakMethod') ifNotNil: [:bm| cogit setBreakMethod: bm]];
  add: (printBytecodeAtEachStep
  ifTrue: ['no print bytecode each bytecode']
  ifFalse: ['print bytecode each bytecode'])
  action: [self ensureDebugAtEachStepBlock.
  printBytecodeAtEachStep := printBytecodeAtEachStep not];
  add: (printFrameAtEachStep
  ifTrue: ['no print frame each bytecode']
  ifFalse: ['print frame each bytecode'])
  action: [self ensureDebugAtEachStepBlock.
  printFrameAtEachStep := printFrameAtEachStep not].
  ^aMenuMorph!

Item was added:
+ ----- Method: Cogit>>cleanUpFailingCogCodeConstituents: (in category 'profiling primitives') -----
+ cleanUpFailingCogCodeConstituents: cogMethodArg
+ <var: #cogMethodArg type: #'CogMethod *'>
+ <inline: #never> "i.e. this should never be called, so keep it out of the main path."
+ | cogMethod |
+ <var: #cogMethod type: #'CogMethod *'>
+ cogMethod := cogMethodArg.
+ [cogMethod < methodZone limitZony] whileTrue:
+ [cogMethod cmType = CMClosedPIC ifTrue:
+ [cogMethod methodObject: 0].
+ cogMethod := methodZone methodAfter: cogMethod].
+ "would like to assert this, but it requires the leak checked be run :-(
+ self assert: self allMachineCodeObjectReferencesValid."
+ coInterpreter popRemappableOop.
+ ^nil!

Item was changed:
  ----- Method: Cogit>>cogCodeConstituents: (in category 'profiling primitives') -----
  cogCodeConstituents: withDetails
  "Answer the contents of the code zone as an array of pair-wise element, address in ascending address order.
  Answer a string for a runtime routine or abstract label (beginning, end, etc), a CompiledMethod for a CMMethod,
+ or a selector (presumably a Symbol) for a PIC.
+ If withDetails is true
+ - answer machine-code to bytecode pc mapping information for methods
+ - answer class, target pair information for closed PIC
+ N.B. Since the class tag for the first case of a closed PIC is stored at the send site, it must be collected
+  by scanning methods (see collectCogConstituentFor:Annotation:Mcpc:Bcpc:Method:).  Since closed PICs
+  are never shared they always come after the method that references them, so we don't need an extra pass
+  to collect the first case class tags, which are (temporarily) assigned to each closed PIC's methodObject field.
+  But we do need to reset the methodObject fields to zero.  This is done in createPICData:, unless memory
+  runs out, in which case it is done by cleanUpFailingCogCodeConstituents:."
- or a selector (presumably a Symbol) for a PIC."
  <api>
  | count cogMethod constituents label value |
  <var: #cogMethod type: #'CogMethod *'>
  count := trampolineTableIndex / 2 + 3. "+ 3 for start, freeStart and end"
  cogMethod := self cCoerceSimple: methodZoneBase to: #'CogMethod *'.
  [cogMethod < methodZone limitZony] whileTrue:
  [cogMethod cmType ~= CMFree ifTrue:
  [count := count + 1].
  cogMethod := methodZone methodAfter: cogMethod].
  constituents := coInterpreter instantiateClass: coInterpreter classArray indexableSize: count * 2.
  constituents ifNil:
  [^constituents].
  coInterpreter pushRemappableOop: constituents.
  ((label := objectMemory stringForCString: 'CogCode') isNil
  or: [(value := self positiveMachineIntegerFor: codeBase) isNil]) ifTrue:
+ [coInterpreter popRemappableOop.
+ ^nil].
- [^nil].
  coInterpreter
+ storePointerUnchecked: 0 ofObject: (self maybeTopRemapped: constituents) withValue: label;
+ storePointerUnchecked: 1 ofObject: (self maybeTopRemapped: constituents) withValue: value.
- storePointerUnchecked: 0 ofObject: coInterpreter topRemappableOop withValue: label;
- storePointerUnchecked: 1 ofObject: coInterpreter topRemappableOop withValue: value.
  0 to: trampolineTableIndex - 1 by: 2 do:
  [:i|
  ((label := objectMemory stringForCString: (trampolineAddresses at: i)) isNil
  or: [(value := self positiveMachineIntegerFor: (trampolineAddresses at: i + 1) asUnsignedInteger) isNil]) ifTrue:
  [coInterpreter popRemappableOop.
  ^nil].
  coInterpreter
+ storePointerUnchecked: 2 + i ofObject: (self maybeTopRemapped: constituents) withValue: label;
+ storePointerUnchecked: 3 + i ofObject: (self maybeTopRemapped: constituents) withValue: value].
- storePointerUnchecked: 2 + i ofObject: coInterpreter topRemappableOop withValue: label;
- storePointerUnchecked: 3 + i ofObject: coInterpreter topRemappableOop withValue: value].
  count := trampolineTableIndex + 2.
  cogMethod := self cCoerceSimple: methodZoneBase to: #'CogMethod *'.
  [cogMethod < methodZone limitZony] whileTrue:
  [cogMethod cmType ~= CMFree ifTrue:
+ [| profileData |
+ profileData := self profileDataFor: cogMethod withDetails: withDetails.
+ profileData ifNil: [^self cleanUpFailingCogCodeConstituents: cogMethod].
+ coInterpreter
- [coInterpreter
  storePointerUnchecked: count
+ ofObject: (self maybeTopRemapped: constituents)
+ withValue: profileData.
- ofObject: coInterpreter topRemappableOop
- withValue: (self valueOf: cogMethod).
  value := withDetails
+ ifTrue: [self collectCogMethodConstituent: cogMethod]
+ ifFalse: [self positiveMachineIntegerFor: cogMethod asUnsignedInteger].
+ value ifNil: [^self cleanUpFailingCogCodeConstituents: cogMethod].
- ifFalse: [self positiveMachineIntegerFor: cogMethod asUnsignedInteger]
- ifTrue: [self collectCogMethodConstituent: cogMethod].
- value ifNil: [coInterpreter popRemappableOop. ^nil].
  coInterpreter
  storePointerUnchecked: count + 1
+ ofObject: (self maybeTopRemapped: constituents)
- ofObject: coInterpreter topRemappableOop
  withValue: value.
  count := count + 2].
  cogMethod := methodZone methodAfter: cogMethod].
  ((label := objectMemory stringForCString: 'CCFree') isNil
  or: [(value := self positiveMachineIntegerFor: methodZone zoneFree) isNil]) ifTrue:
  [coInterpreter popRemappableOop.
  ^nil].
  coInterpreter
+ storePointerUnchecked: count ofObject: (self maybeTopRemapped: constituents) withValue: label;
+ storePointerUnchecked: count + 1 ofObject: (self maybeTopRemapped: constituents) withValue: value.
- storePointerUnchecked: count ofObject: coInterpreter topRemappableOop withValue: label;
- storePointerUnchecked: count + 1 ofObject: coInterpreter topRemappableOop withValue: value.
  ((label := objectMemory stringForCString: 'CCEnd') isNil
  or: [(value := self positiveMachineIntegerFor: methodZone zoneEnd) isNil]) ifTrue:
  [coInterpreter popRemappableOop.
  ^nil].
  coInterpreter
+ storePointerUnchecked: count + 2 ofObject: (self maybeTopRemapped: constituents) withValue: label;
+ storePointerUnchecked: count + 3 ofObject: (self maybeTopRemapped: constituents) withValue: value.
- storePointerUnchecked: count + 2 ofObject: coInterpreter topRemappableOop withValue: label;
- storePointerUnchecked: count + 3 ofObject: coInterpreter topRemappableOop withValue: value.
  constituents := coInterpreter popRemappableOop.
  coInterpreter beRootIfOld: constituents.
+ "would like to assert this, but it requires the leak checked be run :-(
+ self assert: self allMachineCodeObjectReferencesValid."
  ^constituents!

Item was changed:
  ----- Method: Cogit>>collectCogConstituentFor:Annotation:Mcpc:Bcpc:Method: (in category 'profiling primitives') -----
  collectCogConstituentFor: descriptor Annotation: isBackwardBranchAndAnnotation Mcpc: mcpc Bcpc: bcpc Method: cogMethodArg
  <var: #descriptor type: #'BytecodeDescriptor *'>
  <var: #mcpc type: #'char *'>
  <var: #cogMethodArg type: #'void *'>
+ <var: #targetMethod type: #'CogMethod *'>
+ | address entryPoint |
- | address |
  descriptor ifNil: [^0].
  descriptor isMapped ifFalse: [^0].
  address := self positiveMachineIntegerFor: mcpc.
+ address ifNil: [^PrimErrNoMemory]. "This cannot trigger a GC but fails if not enough space in Eden,"
- address ifNil: [^InsufficientCodeSpace]. "We should have a dedicated error code... This cannot trigger a GC but fails if not enough space in Eden,"
  "Assumes we write the values into topRemappableOop"
  coInterpreter
  storePointerUnchecked: cogConstituentIndex
  ofObject: coInterpreter topRemappableOop
  withValue: address.
  coInterpreter
  storePointerUnchecked: cogConstituentIndex + 1
  ofObject: coInterpreter topRemappableOop
+ withValue: (objectMemory integerObjectOf: bcpc).
- withValue: (objectMemory integerObjectOf: bcpc)..
  cogConstituentIndex := cogConstituentIndex + 2.
+
+ "Collect any first case classTags for closed PICs."
+ ((isBackwardBranchAndAnnotation noMask: 1)
+ and: [self isSendAnnotation: isBackwardBranchAndAnnotation >> 1]) ifTrue:
+ [entryPoint := backEnd callTargetFromReturnAddress: mcpc asInteger.
+ entryPoint > methodZoneBase ifTrue: "send is linked"
+ [self targetMethodAndSendTableFor: entryPoint annotation: isBackwardBranchAndAnnotation >> 1 into:
+ [:targetMethod :sendTable|
+  targetMethod cmType = CMClosedPIC ifTrue:
+ [targetMethod methodObject: (objectRepresentation classForInlineCacheTag: (backEnd inlineCacheTagAt: mcpc))]]]].
+ ^0!
- ^ 0!

Item was changed:
  ----- Method: Cogit>>createCPICData: (in category 'profiling primitives') -----
  createCPICData: cPIC
+ "Answer an Array of the PIC's selector, followed by class and targetMethod/doesNotUnderstand: for each entry in the PIC."
  <var: #cPIC type: #'CogMethod *'>
+ | picData |
- | pc entryPoint targetMethod value array |
  <var: #targetMethod type: #'CogMethod *'>
+ self assert: (cPIC methodObject = 0 or: [objectMemory addressCouldBeOop: cPIC methodObject]).
+ picData := objectMemory instantiateClass: objectMemory classArray indexableSize: cPIC cPICNumCases * 2 + 1.
+ picData ifNil: [^picData].
+       objectMemory storePointerUnchecked: 0 ofObject: picData withValue: cPIC selector.
- array := 1.
- array := objectMemory instantiateClass: objectMemory classArray indexableSize: 1 + cPIC cPICNumCases.
-       objectMemory storePointerUnchecked: 0 ofObject: array withValue: cPIC selector.
  1 to: cPIC cPICNumCases do:
+ [:i| | pc entryPoint target targetMethod class |
- [:i|
  pc := self addressOfEndOfCase: i inCPIC: cPIC.
+ i = 1
+ ifTrue:
+ [class := cPIC methodObject. "first case may have been collected and stored here by collectCogConstituentFor:Annotation:Mcpc:Bcpc:Method:"
+ class = 0 ifTrue: [class := objectMemory nilObject]. "cPIC is unreferenced; likely evolved to OpenPIC"
+ entryPoint := backEnd jumpLongTargetBeforeFollowingAddress: pc]
+ ifFalse:
+ [class := objectRepresentation classForInlineCacheTag:
+ (backEnd literal32BeforeFollowingAddress: pc - backEnd jumpLongConditionalByteSize).
+ entryPoint := backEnd jumpLongConditionalTargetBeforeFollowingAddress: pc].
- entryPoint := i = 1
- ifTrue: [backEnd jumpLongTargetBeforeFollowingAddress: pc]
- ifFalse: [backEnd jumpLongConditionalTargetBeforeFollowingAddress: pc].
  "Find target from jump.  A jump to the MNU entry-point should collect #doesNotUnderstand:"
  (cPIC containsAddress: entryPoint)
  ifTrue:
+ [target := objectMemory splObj: SelectorDoesNotUnderstand]
- [value := objectMemory splObj: SelectorDoesNotUnderstand]
  ifFalse:
  [targetMethod := self cCoerceSimple: entryPoint - cmNoCheckEntryOffset to: #'CogMethod *'.
  self assert: targetMethod cmType = CMMethod.
+ target := targetMethod methodObject].
+ objectMemory
+ storePointerUnchecked: i * 2 - 1 ofObject: picData withValue: class;
+ storePointerUnchecked: i * 2 ofObject: picData withValue: target].
+ objectMemory beRootIfOld: picData.
+ cPIC methodObject: 0. "restore invariant."
+ ^picData!
- value := targetMethod methodObject].
- objectMemory storePointer: i ofObject: array withValue: value].
- ^ array!

Item was added:
+ ----- Method: Cogit>>maybeTopRemapped: (in category 'profiling primitives') -----
+ maybeTopRemapped: anOop
+ <inline: true>
+ ^SPURVM ifTrue: [anOop] ifFalse: [objectMemory topRemappableOop]!

Item was added:
+ ----- Method: Cogit>>offsetAndSendTableFoAnnotation:into: (in category 'in-line cacheing') -----
+ offsetAndSendTableFoAnnotation: annotation into: binaryBlock
+ "Find the relevant sendTable for a linked-send with the given annotation.
+ c.f. annotationForSendTable:"
+ <inline: true>
+ | offset sendTable |
+ <var: #sendTable type: #'sqInt *'>
+ annotation = IsSendCall ifTrue:
+ [offset := cmEntryOffset.
+ sendTable := ordinarySendTrampolines] ifFalse:
+ [(BytecodeSetHasDirectedSuperSend and: [annotation = IsDirectedSuperSend]) ifTrue:
+ [offset := cmNoCheckEntryOffset.
+ sendTable := directedSuperSendTrampolines] ifFalse:
+ [(BytecodeSetHasDirectedSuperSend and: [annotation = IsDirectedSuperBindingSend]) ifTrue:
+ [offset := cmNoCheckEntryOffset.
+ sendTable := directedSuperBindingSendTrampolines] ifFalse:
+ [(NewspeakVM and: [annotation = IsNSSelfSend]) ifTrue:
+ [offset := cmEntryOffset.
+ sendTable := selfSendTrampolines] ifFalse:
+ [(NewspeakVM and: [annotation = IsNSDynamicSuperSend]) ifTrue:
+ [offset := cmEntryOffset.
+ sendTable := dynamicSuperSendTrampolines] ifFalse:
+ [self assert: annotation = IsSuperSend.
+ offset := cmNoCheckEntryOffset.
+ sendTable := superSendTrampolines]]]]].
+
+ binaryBlock
+ value: offset
+ value: sendTable!

Item was added:
+ ----- Method: Cogit>>profileDataFor:withDetails: (in category 'profiling primitives') -----
+ profileDataFor: cogMethod withDetails: withDetails
+ "Answers characteristic data for the type of the cogMethod, answering
+ a CompiledMethod for a compiled method,
+ a selector for an open PIC
+ if withDetails then an array containing a selector followed by pairs of class and target method for a closed PIC, otherwise simply a selector."
+ <inline: true>
+ <var: #cogMethod type: #'CogMethod *'>
+ ^cogMethod cmType = CMMethod
+ ifTrue: [cogMethod methodObject]
+ ifFalse: [(withDetails and: [cogMethod cmType = CMClosedPIC])
+ ifTrue: [self createCPICData: cogMethod]
+ ifFalse: [cogMethod selector]]!

Item was removed:
- ----- Method: Cogit>>valueOf: (in category 'profiling primitives') -----
- valueOf: cogMethod
- "gives the type of the cogMethod and returns a CompiledMethod for a compiled method, a selector for an openPIC or an array containing a selector followed by the methods present in the closedPIC for a closedPIC"
-
- <var: #cogMethod type: #'CogMethod *'>
- ^cogMethod cmType = CMMethod
- ifTrue: [cogMethod methodObject]
- ifFalse: [cogMethod cmType = CMClosedPIC
- ifTrue: [self createCPICData: cogMethod.]
- ifFalse: [cogMethod selector]]
-                      !

Item was changed:
  ----- Method: TMethod>>checkedDeclarationAt:put:in: (in category 'accessing') -----
  checkedDeclarationAt: aVariableName put: aDeclaration in: aCCodeGen
  ((args includes: aVariableName)
  or: [(locals includes: aVariableName)
+ or: [(definingClass instVarIndexFor: aVariableName asString ifAbsent: nil) notNil
+ or: [aDeclaration beginsWith: 'extern ']]]) ifFalse:
- or: [(definingClass instVarIndexFor: aVariableName asString ifAbsent: nil) notNil]]) ifFalse:
  [| msg |
  msg := definingClass name, '>>', selector, ' contains declaration for non-existent variable ', aVariableName.
  aCCodeGen
  ifNotNil: [aCCodeGen logger show: msg; cr]
  ifNil: [self error: msg]].
  ^self declarationAt: aVariableName  "<String>" put: aDeclaration!