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

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

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

Name: VMMaker.oscog-eem.2921
Author: eem
Time: 3 January 2021, 6:20:07.965503 pm
UUID: 43202b09-b01d-4ae5-8014-046b5fcead4f
Ancestors: VMMaker.oscog-eem.2920

CoInterpreterMT Simulation:
Provide a Mutex to lock the processor to ensure that simulation traps are executed atomically. Halt any other thread executing machine code while executing a leaf call so that tryLockVMOwnerTo: can run in its won thread without interference.

Make sure that flush flushes transcript output to the screen even if the TranscriptStream preference says otherwise.

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

Item was changed:
  ----- Method: CogThreadManager>>tryLockVMOwnerTo: (in category 'simulation') -----
  tryLockVMOwnerTo: threadIndex
  "In the real VM this is a direct call of Cogit>>#tryLockVMOwnerTo:/ceTryLockVMOwner.
  In the simulation this is where register state is saved and switched, simulaitng a thread switch.
  releaseVM also saves register state.  The code here and in registerState allow us to avoid the
  expensive and complex MultiProcessor hack."
  <doNotGenerate>
+ | result |
- | prior processor result |
  self deny: threadIndex = 0.
+ cogit withProcessorHaltedDo:
+ [| prior processor  |
+ processor := cogit processor.
+ prior := processor registerState.
+ "A thread switch would (have) occur(ed) if it were that the VM were owned other than by threadIndex"
+ vmOwner ~= threadIndex ifTrue:
+ [vmOwner ~= 0 ifTrue:
+ [registerStates at: vmOwner put: prior].
+ processor setRegisterState: (registerStates
+ at: threadIndex
+ ifAbsentPut:
+ [self ensureInitializedProcessor: processor forThreadIndex: threadIndex.
+ processor registerState])].
+ result := cogit tryLockVMOwnerTo: threadIndex.
+ self assert: result = (threadIndex = vmOwner).
+ registerStates at: threadIndex put: processor registerState.
+ threadIndex ~= vmOwner ifTrue: "the lock attempt failed; undo the (processor) thread switch."
+ [processor setRegisterState: prior]].
- processor := cogit processor.
- prior := processor registerState.
- "A thread switch would (have) occur(ed) if it were that the VM were owned other than by threadIndex"
- vmOwner ~= threadIndex ifTrue:
- [vmOwner ~= 0 ifTrue:
- [registerStates at: vmOwner put: prior].
- processor setRegisterState: (registerStates
- at: threadIndex
- ifAbsentPut:
- [self ensureInitializedProcessor: processor forThreadIndex: threadIndex.
- processor registerState])].
- result := cogit tryLockVMOwnerTo: threadIndex.
- self assert: result = (threadIndex = vmOwner).
- registerStates at: threadIndex put: processor registerState.
- threadIndex ~= vmOwner ifTrue: "the lock attempt failed; undo the (processor) thread switch."
- [processor setRegisterState: prior].
  ^result!

Item was changed:
  ----- Method: CogVMSimulator>>flush (in category 'debug printing') -----
  flush
+ traceOn ifTrue:
+ [transcript flush.
+ "We *always* want to make output visible on flush"
+ TranscriptStream forceUpdate ifFalse:
+ [transcript changed: #appendEntry]]!
- <cmacro: '() fflush(stdout)'>
- traceOn ifTrue: [transcript flush]!

Item was changed:
  CogClass subclass: #Cogit
(excessive size, no diff calculated)

Item was changed:
  ----- Method: Cogit>>handleCallOrJumpSimulationTrap: (in category 'simulation only') -----
  handleCallOrJumpSimulationTrap: aProcessorSimulationTrap
  <doNotGenerate>
  | evaluable function memory result savedFramePointer savedStackPointer savedArgumentCount retpc |
+ "Execution of a single instruction must be within the processorLock critical section to ensure
+ simulation traps are executed atomically.  However, at this point control is leaving machine
+ code and entering the run-time and hence the lock must be released."
+ processorLock primitiveExitCriticalSection.
-
  "This is a hack fix before we revise the simulators.  When a jump call is made, the next
  pc is effectively the return address on the stack, not the instruction following the jump."
  aProcessorSimulationTrap type == #jump ifTrue:
  [processor hackFixNextPCOfJumpFor: aProcessorSimulationTrap using: objectMemory].
 
  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: "this is for invoking ARMv5 floating-point intrinsics"
  [^self handleABICallOrJumpSimulationTrap: aProcessorSimulationTrap evaluable: evaluable].
  evaluable selector].
  memory := coInterpreter memory.
  function == #interpret ifTrue: "i.e. we're here via ceInvokeInterpret/ceReturnToInterpreterTrampoline and should discard all state back to enterSmalltalkExecutiveImplementation"
  [self recordInstruction: {'(simulated jump call of '. aProcessorSimulationTrap address. '/'. function. ')'}.
  "self halt: evaluable selector."
    clickConfirm ifTrue:
  [(self confirm: 'skip jump to interpret?') ifFalse:
  [clickConfirm := false. self halt]].
  processor simulateJumpCallOf: aProcessorSimulationTrap address memory: memory.
  coInterpreter reenterInterpreter.
  "NOTREACHED"
  self halt].
  function ~~ #ceBaseFrameReturn: ifTrue:
  [coInterpreter assertValidExternalStackPointers].
  (backEnd wantsNearAddressFor: function) ifTrue:
  [^self perform: function with: aProcessorSimulationTrap].
  processor
  simulateCallOf: aProcessorSimulationTrap address
  nextpc: aProcessorSimulationTrap nextpc
  memory: memory.
  retpc := processor retpcIn: memory.
  self recordInstruction: {'(simulated call of '. aProcessorSimulationTrap address. '/'. function. ')'}.
  savedFramePointer := coInterpreter framePointer.
  savedStackPointer := coInterpreter stackPointer.
  savedArgumentCount := coInterpreter argumentCount.
  result := ["self halt: evaluable selector."
      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: #continueNoReturn].
 
  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 primFailCode = 0
  ifTrue: [(CogVMSimulator stackAlteringPrimitives 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. ')'}.
  processor simulateReturnIn: memory.
  self assert: processor pc = retpc.
  processor smashCallerSavedRegistersWithValuesFrom: 16r80000000 by: objectMemory wordSize].
  self assert: (result isInteger "an oop result"
  or: [result == coInterpreter
  or: [result == objectMemory
  or: [result == nil
  or: [result == #continueNoReturn]]]]).
  processor cResultRegister: (result
  ifNil: [0]
  ifNotNil: [result isInteger
  ifTrue: [result]
  ifFalse: [16rF00BA222]])!

Item was changed:
  ----- Method: Cogit>>initializeProcessor (in category 'initialization') -----
  initializeProcessor
  "Initialize the simulation processor, arranging that its initial stack is somewhere on the rump C stack."
  <doNotGenerate>
  guardPageSize := self class guardPageSize.
  lastNInstructions := OrderedCollection new.
  processor initializeStackFor: self.
  self initializeProcessorStack: coInterpreter rumpCStackAddress.
  coInterpreter setCFramePointer: processor fp setCStackPointer: processor sp.
  (InitializationOptions at: #UseMultiProcessor ifAbsent: [false]) ifTrue:
+ [processor := MultiProcessor for: processor coInterpreter: coInterpreter].
+ processorLock := Mutex new!
- [processor := MultiProcessor for: processor coInterpreter: coInterpreter]!

Item was changed:
  ----- Method: Cogit>>simulateCogCodeAt: (in category 'simulation only') -----
  simulateCogCodeAt: address "<Integer>"
  <doNotGenerate>
  | stackZoneBase |
  stackZoneBase := coInterpreter stackZoneBase.
  processor pc: address.
  [[[singleStep
  ifTrue:
  [[processor sp < stackZoneBase ifTrue: [self halt].
   self recordProcessing.
   self maybeBreakAt: processor pc] value. "So that the Debugger's Over steps over all this"
+  processorLock critical:
+ [processor
-  processor
  singleStepIn: coInterpreter memory
  minimumAddress: guardPageSize
+ readOnlyBelow: methodZone zoneEnd]]
- readOnlyBelow: methodZone zoneEnd]
  ifFalse:
+ [processorLock critical:
+ [processor
- [processor
  runInMemory: coInterpreter memory
  minimumAddress: guardPageSize
+ readOnlyBelow: methodZone zoneEnd]].
- readOnlyBelow: methodZone zoneEnd].
    "((printRegisters or: [printInstructions]) and: [clickConfirm]) ifTrue:
  [(self confirm: 'continue?') ifFalse:
  [clickConfirm := false. self halt]]."
    true] whileTrue]
  on: ProcessorSimulationTrap
  do: [:ex| ex applyTo: self].
  true] whileTrue!

Item was changed:
  ----- Method: Cogit>>simulateLeafCallOf: (in category 'simulation only') -----
  simulateLeafCallOf: someFunction
  "Simulate execution of machine code that leaf-calls someFunction,
  answering the result returned by someFunction."
  "CogProcessorAlienInspector openFor: coInterpreter"
  <doNotGenerate>
  | priorSP priorPC priorLR spOnEntry bogusRetPC |
  self recordRegisters.
  priorSP := processor sp.
  priorPC := processor pc.
  priorLR := backEnd hasLinkRegister ifTrue: [processor lr].
  processor
  simulateLeafCallOf: someFunction
  nextpc: (bogusRetPC := 16rBADF00D5 roundTo: backEnd codeGranularity)
  memory: coInterpreter memory.
  spOnEntry := processor sp.
  self recordInstruction: {'(simulated call of '. someFunction. ')'}.
+ ^[[[processor pc between: self class guardPageSize and: methodZone zoneEnd] whileTrue:
+ [singleStep
- ^[[processor pc between: self class guardPageSize and: methodZone zoneEnd] whileTrue:
- [[singleStep
  ifTrue: [self recordProcessing.
  self maybeBreakAt: processor pc.
+ processorLock critical:
+ [processor
+ singleStepIn: coInterpreter memory
+ minimumAddress: guardPageSize
+ readOnlyBelow: methodZone zoneEnd]]
+ ifFalse: [processorLock critical:
+ [processor
+ runInMemory: coInterpreter memory
+ minimumAddress: guardPageSize
+ readOnlyBelow: methodZone zoneEnd]]]]
- processor
- singleStepIn: coInterpreter memory
- minimumAddress: guardPageSize
- readOnlyBelow: methodZone zoneEnd]
- ifFalse: [processor
- runInMemory: coInterpreter memory
- minimumAddress: guardPageSize
- readOnlyBelow: methodZone zoneEnd]]
  on: ProcessorSimulationTrap, Error
  do: [:ex|
  "Again this is a hack for the processor simulators not properly simulating returns to bogus addresses.
  In this case BochsX64Alien doesn't do the right thing."
  processor pc = bogusRetPC ifTrue:
  [self recordInstruction: {'(simulated (real) return to '. processor pc. ')'}.
  ^processor cResultRegister].
  ex isProcessorSimulationTrap ifFalse:
  [ex pass].
  ex applyTo: self.
  ex type == #return ifTrue:
+ [^processor cResultRegister]].
- [^processor cResultRegister]]].
  processor pc = bogusRetPC ifTrue:
  [self recordInstruction: {'(simulated (real) return to '. processor pc. ')'}].
  processor cResultRegister]
  ensure:
  [processor sp: priorSP.
  processor pc: priorPC.
  priorLR ifNotNil: [:lr| processor lr: lr]]!

Item was changed:
  ----- Method: Cogit>>tryLockVMOwnerTo: (in category 'multi-threading') -----
  tryLockVMOwnerTo: value
  <api>
  "ceTryLockVMOwner does an atomic compare-and-swap of the vmOwner
  variable with zero and the argument, setting vmOwner to value if it was
  zero. It answers if the lock was zero and hence was acquired.
 
  See CogThreadManager>>#tryLockVMOwnerTo: for the simulation of
  processor thread switching which surrounds this method."
  <cmacro: '(value) ceTryLockVMOwner(value)'>
+ | breakPCWasTrue |
+ (thisContext findContextSuchThat: [:ctxt| ctxt selector == #primitiveRelinquishProcessor]) ifNil:
+ [self halt].
+ (breakPCWasTrue := breakPC == true) ifTrue:
+ [breakPC := nil].
  processor abiMarshalArg0: value in: objectMemory memory.
  ^[ | result |
  result := self simulateLeafCallOf: ceTryLockVMOwner.
  self assert: (result ~= 0) = (coInterpreter threadManager getVMOwner = value).
  result ~= 0] ensure:
+ [processor abiUnmarshal: 1.
+ breakPCWasTrue ifTrue:
+ [breakPC := true]]!
- [processor abiUnmarshal: 1]!

Item was added:
+ ----- Method: Cogit>>withProcessorHaltedDo: (in category 'simulation processor access') -----
+ withProcessorHaltedDo: aBlock
+ ^processorLock critical:
+ [| oldBreakPC oldSingleStep |
+ oldBreakPC := breakPC.
+ oldSingleStep := singleStep.
+ breakPC := singleStep := true.
+ aBlock ensure:
+ [singleStep := oldSingleStep.
+ breakPC := oldBreakPC]]!

Item was changed:
  ----- Method: StackInterpreterSimulator>>flush (in category 'debug printing') -----
  flush
+ traceOn ifTrue:
+ [transcript flush.
+ "We *always* want to make output visible on flush"
+ TranscriptStream forceUpdate ifFalse:
+ [transcript changed: #appendEntry]]!
- traceOn ifTrue: [transcript flush]!