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

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

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

Name: VMMaker.oscog-eem.2625
Author: eem
Time: 21 December 2019, 3:08:54.005535 pm
UUID: f5116739-cb0e-4ec3-a35c-f6320b6acb4a
Ancestors: VMMaker.oscog-eem.2624

Cogit:
Split the generation of translated hashMultiply into a SmallInteger version and a Large(Positive)Integer version.

Simulator:
Have simulation treat mcprim invocation as a laft call, and get this to work properly.

Fix the break block's prompt.

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

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: CFramePointer];
  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 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 strncmp: s
  _: (m selector + objectMemory baseHeaderSize)
  _: (objectMemory numBytesOf: m selector)) = 0]]) ifTrue:
  [cogit printCogMethod: m]]]];
  add: 'print cog methods with method...' action:
  [(self promptHex: 'method') ifNotNil: [:methodOop| cogMethodZone printCogMethodsWithMethod: methodOop]];
  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: '[:address| false]'.
- 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 changed:
  ----- Method: Cogit>>handleCallOrJumpSimulationTrap: (in category 'simulation only') -----
  handleCallOrJumpSimulationTrap: aProcessorSimulationTrap
  <doNotGenerate>
+ | evaluable function memory result savedFramePointer savedStackPointer savedArgumentCount leaf |
- | evaluable function memory result savedFramePointer savedStackPointer savedArgumentCount rpc |
  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)
- [(coInterpreter mcprims includes: function)
  ifTrue:
  [processor
  simulateLeafCallOf: aProcessorSimulationTrap address
  nextpc: aProcessorSimulationTrap nextpc
  memory: memory]
  ifFalse:
  [processor
  simulateCallOf: aProcessorSimulationTrap address
  nextpc: aProcessorSimulationTrap nextpc
  memory: memory].
  self recordInstruction: {'(simulated call of '. aProcessorSimulationTrap address. '/'. function. ')'}]
  ifFalse:
+ [leaf := false.
+ processor
- [processor
  simulateJumpCallOf: aProcessorSimulationTrap address
  memory: memory.
  self recordInstruction: {'(simulated jump to '. aProcessorSimulationTrap address. '/'. function. ')'}].
  savedFramePointer := coInterpreter framePointer.
  savedStackPointer := coInterpreter stackPointer.
  savedArgumentCount := coInterpreter argumentCount.
  result := ["self halt: evaluable selector."
      ((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
- rpc := processor retpcIn: memory.
- self assert: (rpc >= codeBase and: [rpc < methodZone freeStart]).
- processor smashCallerSavedRegistersWithValuesFrom: 16r80000000 by: objectMemory wordSize in: memory.
- (coInterpreter mcprims includes: function)
  ifTrue: [processor simulateLeafReturnIn: memory]
+ ifFalse: [processor simulateReturnIn: memory].
+ self assert: (processor pc between: codeBase and: methodZone freeStart).
+ processor smashCallerSavedRegistersWithValuesFrom: 16r80000000 by: objectMemory wordSize in: memory].
- ifFalse: [processor simulateReturnIn: 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: SimpleStackBasedCogit>>genPrimitiveHashMultiply (in category 'primitive generators') -----
  genPrimitiveHashMultiply
  "Implement 28-bit hashMultiply for SmallInteger and LargePositiveInteger receivers."
+ | jmpFailImm jmpFailNotPositiveLargeInt |
- | jmpFailImm jmpFailNonImm jmpNotSmallInt reenter |
  backEnd canMulRR ifFalse:
  [^UnimplementedPrimitive].
 
+ self mclassIsSmallInteger ifTrue:
+ [objectRepresentation genConvertSmallIntegerToIntegerInReg: ReceiverResultReg.
+ self MoveCq: HashMultiplyConstant R: TempReg.
+ self MulR: TempReg R: ReceiverResultReg.
+ self AndCq: HashMultiplyMask R: ReceiverResultReg.
+ objectRepresentation genConvertIntegerToSmallIntegerInReg: ReceiverResultReg.
+ self RetN: 0.
+ ^0].
- jmpNotSmallInt := objectRepresentation genJumpNotSmallInteger: ReceiverResultReg.
 
+ "This check is necessary.  LargeNegativeInteger is a subclass of LargePositiveInteger in Squeak, Pharo, Cuis, et al."
+ jmpFailImm := objectRepresentation genJumpImmediate: ReceiverResultReg.
+ objectRepresentation genGetCompactClassIndexNonImmOf: ReceiverResultReg into: ClassReg.
+ self CmpCq: ClassLargePositiveIntegerCompactIndex R: ClassReg.
+ jmpFailNotPositiveLargeInt := self JumpNonZero: 0.
+ objectRepresentation genLoadSlot: 0 sourceReg: ReceiverResultReg destReg: ReceiverResultReg.
- objectRepresentation genConvertSmallIntegerToIntegerInReg: ReceiverResultReg.
- reenter :=
  self MoveCq: HashMultiplyConstant R: TempReg.
  self MulR: TempReg R: ReceiverResultReg.
  self AndCq: HashMultiplyMask R: ReceiverResultReg.
  objectRepresentation genConvertIntegerToSmallIntegerInReg: ReceiverResultReg.
  self RetN: 0.
 
+ jmpFailImm jmpTarget: (jmpFailNotPositiveLargeInt jmpTarget: self Label).
- jmpNotSmallInt jmpTarget: self Label.
- jmpFailImm := objectRepresentation genJumpImmediate: ReceiverResultReg.
- objectRepresentation genGetCompactClassIndexNonImmOf: ReceiverResultReg into: ClassReg.
- self CmpCq: ClassLargePositiveIntegerCompactIndex R: ClassReg.
- jmpFailNonImm := self JumpNonZero: 0.
- objectRepresentation genLoadSlot: 0 sourceReg: ReceiverResultReg destReg: ReceiverResultReg.
- self Jump: reenter.
-
- jmpFailImm jmpTarget: (jmpFailNonImm jmpTarget: self Label).
  ^0!