VM Maker: VMMaker.oscog-eem.2639.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.2639.mcz

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

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

Name: VMMaker.oscog-eem.2639
Author: eem
Time: 27 December 2019, 7:43:55.854755 pm
UUID: 57f623a3-5133-4554-8f54-01e80e1239cb
Ancestors: VMMaker.oscog-eem.2638

Simulation/Debugging:
Print a mehtod's methodClass (name) in the list of cog methods.
Close any open debuggers on the VM simulator when closing the simulaiton window.
Always ask whether to skip a run-time call when click-stepping.
Add a proceed click to click-step.

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

Item was changed:
  ----- Method: CoInterpreter>>printCogMethod: (in category 'debug printing') -----
  printCogMethod: cogMethod
  <api>
  <var: #cogMethod type: #'CogMethod *'>
  | address primitive |
  self cCode: ''
  inSmalltalk:
  [self transcript ensureCr.
  cogMethod isInteger ifTrue:
  [^self printCogMethod: (self cCoerceSimple: cogMethod to: #'CogMethod *')]].
  address := cogMethod asInteger.
  self printHex: address;
  print: ' <-> ';
  printHex: address + cogMethod blockSize.
  cogMethod cmType = CMMethod ifTrue:
  [self print: ': method: ';
  printHex: cogMethod methodObject.
  primitive := self primitiveIndexOfMethod: cogMethod methodObject
  header: cogMethod methodHeader.
  primitive ~= 0 ifTrue:
+ [self print: ' prim '; printNum: primitive].
+ ((objectMemory addressCouldBeObj: cogMethod methodObject)
+ and: [objectMemory addressCouldBeObj: (self methodClassOf: cogMethod methodObject)]) ifTrue:
+ [self space; printNameOfClass: (self methodClassOf: cogMethod methodObject) count: 2]].
- [self print: ' prim '; printNum: primitive]].
  cogMethod cmType = CMBlock ifTrue:
  [self print: ': block home: ';
  printHex: (self cCoerceSimple: cogMethod to: #'CogBlockMethod *') cmHomeMethod asUnsignedInteger].
  cogMethod cmType = CMClosedPIC ifTrue:
  [self print: ': Closed PIC N: ';
  printHex: cogMethod cPICNumCases].
  cogMethod cmType = CMOpenPIC ifTrue:
  [self print: ': Open PIC '].
  self print: ' selector: '; printHex: cogMethod selector.
  cogMethod selector = objectMemory nilObject
  ifTrue: [| s |
  (cogMethod cmType = CMMethod
  and: [(s := self maybeSelectorOfMethod: cogMethod methodObject) notNil])
  ifTrue: [self print: ' (nil: '; printStringOf: s; print: ')']
  ifFalse: [self print: ' (nil)']]
  ifFalse: [self space; printStringOf: cogMethod selector].
  self cr!

Item was added:
+ ----- Method: CogMethodZone>>addressIsLikelyCogMethod: (in category 'testing') -----
+ addressIsLikelyCogMethod: address
+ <doNotGenerate>
+ (address anyMask: (self roundUpLength: 1) - 1) ifTrue:
+ [^false].
+ (self oop: address isGreaterThanOrEqualTo: cogit minCogMethodAddress andLessThan: mzFreeStart) ifFalse:
+ [^false].
+ ^(objectMemory baseHeader: address) = objectMemory nullHeaderForMachineCodeMethod!

Item was changed:
  ----- Method: CogVMSimulator>>close (in category 'initialization') -----
  close  "close any files that ST may have opened, etc"
  pluginList do: [:assoc| | plugin | plugin := assoc value. plugin ~~ self ifTrue: [plugin close]].
+ "Ugh; at least some of this code belongs in the UI..."
- "Ugh; this code belongs in the UI"
  World submorphs do:
  [:submorph|
  (submorph model isVMObjectInspector
  and: [submorph model coInterpreter == self]) ifTrue:
+ [submorph delete].
+ (submorph model isDebugger
+ and: [submorph model interruptedProcess suspendedContext findContextSuchThat:
+ [:ctxt|
+ (ctxt receiver == cogit
+ and: [ctxt selector == #simulateCogCodeAt:])
+ or: [ctxt receiver == self
+ and: [ctxt selector == #interpret]]]]) notNil ifTrue:
  [submorph delete]]!

Item was added:
+ ----- Method: CogVMSimulator>>printCallStack (in category 'debug printing') -----
+ printCallStack
+ <inline: false>
+ cogit headFramePointer
+ ifNil: [self printCallStackOf: (objectMemory fetchPointer: SuspendedContextIndex ofObject: self activeProcess)]
+ ifNotNil: [:fp| self printCallStackFP: fp]!

Item was changed:
  ----- Method: CogVMSimulator>>printChar: (in category 'debug printing') -----
  printChar: aByte
 
+ traceOn ifTrue:
+ [(aByte between: 0 and: 255)
+ ifTrue: [transcript nextPut: aByte asCharacter]
+ ifFalse: [transcript nextPutAll: 'BAD CHARACTER '.
+ aByte printOn: transcript base: 16]]!
- traceOn ifTrue: [ transcript nextPut: aByte asCharacter ].!

Item was added:
+ ----- Method: CogVMSimulator>>printStackCallStack (in category 'debug printing') -----
+ printStackCallStack
+ <doNotGenerate>
+ self printStackCallStackOf: cogit headFramePointer!

Item was changed:
  ----- Method: Cogit>>handleABICallOrJumpSimulationTrap:evaluable: (in category 'simulation only') -----
  handleABICallOrJumpSimulationTrap: aProcessorSimulationTrap evaluable: evaluable
  <doNotGenerate>
 
  self assert: aProcessorSimulationTrap type = #call.
  processor
  simulateLeafCallOf: aProcessorSimulationTrap address
  nextpc: aProcessorSimulationTrap nextpc
  memory: coInterpreter memory.
  self recordInstruction: {'(simulated call of '. aProcessorSimulationTrap address. '/'. evaluable selector. ')'}.
+ clickConfirm ifTrue:
- ((printRegisters or: [printInstructions]) and: [clickConfirm]) ifTrue:
    [(self confirm: 'skip run-time call?') ifFalse:
  [clickConfirm := false. self halt]].
  evaluable valueWithArguments: (processor
  postCallArgumentsNumArgs: evaluable numArgs
  in: coInterpreter memory).
  self recordInstruction: {'(simulated return to '. processor retpcIn: coInterpreter memory. ')'}.
  processor
  smashABICallerSavedRegistersWithValuesFrom: 16r80000000 by: objectMemory wordSize;
  simulateLeafReturnIn: coInterpreter memory!

Item was changed:
  ----- Method: Cogit>>handleCallOrJumpSimulationTrap: (in category 'simulation only') -----
  handleCallOrJumpSimulationTrap: aProcessorSimulationTrap
  <doNotGenerate>
  | evaluable function memory result savedFramePointer savedStackPointer savedArgumentCount leaf retpc |
  evaluable := simulatedTrampolines
  at: aProcessorSimulationTrap address
  ifAbsent: [self errorProcessingSimulationTrap: aProcessorSimulationTrap
  in: simulatedTrampolines].
  function := evaluable isBlock
  ifTrue: ['aBlock; probably some plugin primitive']
  ifFalse:
  [evaluable receiver == backEnd ifTrue:
  [^self handleABICallOrJumpSimulationTrap: aProcessorSimulationTrap evaluable: evaluable].
  evaluable selector].
  function ~~ #ceBaseFrameReturn: ifTrue:
  [coInterpreter assertValidExternalStackPointers].
  (backEnd wantsNearAddressFor: function) ifTrue:
  [^self perform: function with: aProcessorSimulationTrap].
  memory := coInterpreter memory.
  aProcessorSimulationTrap type == #call
  ifTrue:
  [(leaf := coInterpreter mcprims includes: function)
  ifTrue:
  [processor
  simulateLeafCallOf: aProcessorSimulationTrap address
  nextpc: aProcessorSimulationTrap nextpc
  memory: memory.
  retpc := processor leafRetpcIn: memory]
  ifFalse:
  [processor
  simulateCallOf: aProcessorSimulationTrap address
  nextpc: aProcessorSimulationTrap nextpc
  memory: memory.
  retpc := processor retpcIn: memory].
  self recordInstruction: {'(simulated call of '. aProcessorSimulationTrap address. '/'. function. ')'}]
  ifFalse:
  [leaf := false.
  processor
  simulateJumpCallOf: aProcessorSimulationTrap address
  memory: memory.
  retpc := processor retpcIn: memory. "sideways call; the primitive has pushed a return address."
  self recordInstruction: {'(simulated jump to '. aProcessorSimulationTrap address. '/'. function. ')'}].
  savedFramePointer := coInterpreter framePointer.
  savedStackPointer := coInterpreter stackPointer.
  savedArgumentCount := coInterpreter argumentCount.
  result := ["self halt: evaluable selector."
+     clickConfirm ifTrue:
-     ((printRegisters or: [printInstructions]) and: [clickConfirm]) ifTrue:
  [(self confirm: 'skip run-time call?') ifFalse:
  [clickConfirm := false. self halt]].
    evaluable valueWithArguments: (processor
  postCallArgumentsNumArgs: evaluable numArgs
  in: memory)]
  on: ReenterMachineCode
  do: [:ex| ex return: ex returnValue].
 
  coInterpreter assertValidExternalStackPointers.
  "Verify the stack layout assumption compileInterpreterPrimitive: makes, provided we've
  not called something that has built a frame, such as closure value or evaluate method, or
  switched frames, such as primitiveSignal, primitiveWait, primitiveResume, primitiveSuspend et al."
  (function beginsWith: 'primitive') ifTrue:
  [coInterpreter checkForLastObjectOverwrite.
  coInterpreter primFailCode = 0
  ifTrue: [(#( primitiveClosureValue primitiveClosureValueWithArgs primitiveClosureValueNoContextSwitch
  primitiveFullClosureValue primitiveFullClosureValueWithArgs primitiveFullClosureValueNoContextSwitch
  primitiveSignal primitiveWait primitiveResume primitiveSuspend primitiveYield
  primitiveExecuteMethodArgsArray primitiveExecuteMethod
  primitivePerform primitivePerformWithArgs primitivePerformInSuperclass
  primitiveTerminateTo primitiveStoreStackp primitiveDoPrimitiveWithArgs)
  includes: function) ifFalse:
  ["This is a rare case (e.g. in Scorch where a married context's sender is set to nil on trapTrpped and hence the stack layout is altered."
  (function == #primitiveSlotAtPut and: [objectMemory isContext: (coInterpreter frameReceiver: coInterpreter framePointer)]) ifFalse:
  [self assert: savedFramePointer = coInterpreter framePointer.
  self assert: savedStackPointer + (savedArgumentCount * objectMemory wordSize)
  = coInterpreter stackPointer]]]
  ifFalse:
  [self assert: savedFramePointer = coInterpreter framePointer.
  self assert: savedStackPointer = coInterpreter stackPointer]].
  result ~~ #continueNoReturn ifTrue:
  [self recordInstruction: {'(simulated return to '. processor retpcIn: memory. ')'}.
  leaf
  ifTrue: [processor simulateLeafReturnIn: memory]
  ifFalse: [processor simulateReturnIn: memory].
  self assert: processor pc = retpc.
  processor smashCallerSavedRegistersWithValuesFrom: 16r80000000 by: objectMemory wordSize in: memory].
  self assert: (result isInteger "an oop result"
  or: [result == coInterpreter
  or: [result == objectMemory
  or: [#(nil continue continueNoReturn) includes: result]]]).
  processor cResultRegister: (result
  ifNil: [0]
  ifNotNil: [result isInteger
  ifTrue: [result]
  ifFalse: [16rF00BA222]])
 
  "coInterpreter cr.
  processor sp + 32 to: processor sp - 32 by: -4 do:
  [:sp|
  sp = processor sp
  ifTrue: [coInterpreter print: 'sp->'; tab]
  ifFalse: [coInterpreter printHex: sp].
  coInterpreter tab; printHex: (coInterpreter longAt: sp); cr]"!

Item was changed:
  ----- Method: Cogit>>promptForBreakPC (in category 'simulation only') -----
  promptForBreakPC
  <doNotGenerate>
  | s first pc |
  s := UIManager default request: 'Break pc (hex, + to add, - to remove)'.
  s := s withBlanksTrimmed.
  s isEmpty ifTrue: [^self].
  ('+-' includes: s first) ifTrue: [first := s first. s := s allButFirst].
  (s isEmpty and: [first = $-]) ifTrue:
  [^self breakPC: nil].
  pc := (s includes: $r)
  ifTrue:
  [Number readFrom: s readStream]
  ifFalse:
  [(#('0x' '-0x') detect: [:prefix| s beginsWith: prefix] ifNone: []) ifNotNil:
  [:prefix|
  s := s allButFirst: prefix size.
  prefix first = $- ifTrue: [s := '-', s]].
  Integer readFrom: s readStream base: 16].
+ ((methodZone addressIsLikelyCogMethod: pc)
+ and: [UIManager confirm: 'pc is method; interpret as no check entry point?']) ifTrue:
+ [pc := pc + cmNoCheckEntryOffset].
  first = $+ ifTrue:
  [^self breakPC: (breakPC addBreakpoint: pc)].
  first = $- ifTrue:
  [^self breakPC: (breakPC removeBreakpoint: pc)].
  self breakPC: pc!