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

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

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

Name: VMMaker.oscog-eem.2058
Author: eem
Time: 29 December 2016, 5:25:46.509315 pm
UUID: 0404f168-043b-4376-89e3-1340adf9c797
Ancestors: VMMaker.oscog-eem.2057

Simulator:
Add a Processor yield to doSignalExternalSemaphores: so that e.g. background processes in teh SocketPluginSimulator will get a chance to run more frequently than if ythe yield we in ioProcessEvents.

Fix the new implementation of asCharPtr; it should coerce the firstIndexableField:.

Fix the new generic plugin closing.

Implement windowIsClosing in the stack interpreter sim.

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

Item was changed:
  CoInterpreterMT subclass: #CogVMSimulator
+ instanceVariableNames: 'parent enableCog byteCount lastPollCount lastExtPC sendCount lookupCount printSends traceOn myBitBlt displayForm fakeForm imageName pluginList mappedPluginEntries quitBlock transcript displayView eventTransformer printFrameAtEachStep printBytecodeAtEachStep systemAttributes uniqueIndices uniqueIndex breakCount atEachStepBlock startMicroseconds lastYieldMicroseconds externalSemaphoreSignalRequests externalSemaphoreSignalResponses extSemTabSize debugStackDepthDictionary performFilters eventQueue expectedSends expecting'
- instanceVariableNames: 'parent enableCog byteCount lastPollCount lastExtPC sendCount lookupCount printSends traceOn myBitBlt displayForm fakeForm imageName pluginList mappedPluginEntries quitBlock transcript displayView eventTransformer printFrameAtEachStep printBytecodeAtEachStep systemAttributes uniqueIndices uniqueIndex breakCount atEachStepBlock startMicroseconds externalSemaphoreSignalRequests externalSemaphoreSignalResponses extSemTabSize debugStackDepthDictionary performFilters eventQueue expectedSends expecting'
  classVariableNames: 'ByteCountsPerMicrosecond ExpectedSends'
  poolDictionaries: ''
  category: 'VMMaker-JITSimulation'!
 
  !CogVMSimulator commentStamp: 'eem 9/3/2013 11:16' prior: 0!
  This class defines basic memory access and primitive simulation so that the CoInterpreter can run simulated in the Squeak environment.  It also defines a number of handy object viewing methods to facilitate pawing around in the object memory.  Remember that you can test the Cogit using its class-side in-image compilation facilities.
 
  To see the thing actually run, you could (after backing up this image and changes), execute
 
  (CogVMSimulator new openOn: Smalltalk imageName) test
 
  and be patient both to wait for things to happen, and to accept various things that may go wrong depending on how large or unusual your image may be.  We usually do this with a small and simple benchmark image.
 
  Here's an example to launch the simulator in a window.  The bottom-right window has a menu packed with useful stuff:
 
  (CogVMSimulator newWithOptions: #(Cogit StackToRegisterMappingCogit))
  desiredNumStackPages: 8;
  openOn: '/Users/eliot/Cog/startreader.image';
  openAsMorph;
  run
 
  Here's a hairier example that I (Eliot) actually use in daily development with some of the breakpoint facilities commented out.
 
  | cos proc opts |
  CoInterpreter initializeWithOptions: (opts := Dictionary newFromPairs: #(Cogit StackToRegisterMappingCogit)).
  CogVMSimulator chooseAndInitCogitClassWithOpts: opts.
  cos := CogVMSimulator new.
  "cos initializeThreadSupport." "to test the multi-threaded VM"
  cos desiredNumStackPages: 8. "to set the size of the stack zone"
  "cos desiredCogCodeSize: 8 * 1024 * 1024." "to set the size of the Cogit's code zone"
  cos openOn: '/Users/eliot/Squeak/Squeak4.4/trunk44.image'. "choose your favourite image"
  "cos setBreakSelector: 'r:degrees:'." "set a breakpoint at a specific selector"
  proc := cos cogit processor.
  "cos cogit sendTrace: 7." "turn on tracing"
  "set a complex breakpoint at a specific point in machine code"
  "cos cogit singleStep: true; breakPC: 16r56af; breakBlock: [:cg|  cos framePointer > 16r101F3C and: [(cos longAt: cos framePointer - 4) = 16r2479A and: [(cos longAt: 16r101F30) = (cos longAt: 16r101F3C) or: [(cos longAt: 16r101F2C) = (cos longAt: 16r101F3C)]]]]; sendTrace: 1".
  "[cos cogit compilationTrace: -1] on: MessageNotUnderstood do: [:ex|]." "turn on compilation tracing in the StackToRegisterMappingCogit"
  "cos cogit setBreakMethod: 16rB38880."
  cos
  openAsMorph;
  "toggleTranscript;" "toggleTranscript will send output to the Transcript instead of the morph's rather small window"
  halt;
  run!

Item was changed:
  ----- Method: CogVMSimulator>>close (in category 'initialization') -----
  close  "close any files that ST may have opened, etc"
+ pluginList do: [:plugin| plugin ~~ self ifTrue: [plugin close]]!
- pluginList do: [:plugin| (plugin ~~ self and: [plugin respondsTo: #close]) ifTrue: [plugin close]]!

Item was changed:
  ----- Method: CogVMSimulator>>doSignalExternalSemaphores: (in category 'process primitive support') -----
  doSignalExternalSemaphores: minTableSize
  "This is a non-thread-safe simulation.  See platforms/Cross/vm/sqExternalSemaphores.c
+ for the real code.  For the benefit of the SocketPluginSimulator, do a yield every 100
+ virtual microseconds."
+ | now switched |
+ now := self ioUTCMicroseconds.
+ now - lastYieldMicroseconds >= 100 ifTrue:
+ [lastYieldMicroseconds := now.
+ Processor yield].
+
- for the real code."
- | switched |
  switched := false.
  1 to: (minTableSize min: externalSemaphoreSignalRequests size) do:
  [:i| | responses |
  responses := externalSemaphoreSignalResponses at: i.
  [responses < (externalSemaphoreSignalRequests at: i)] whileTrue:
  [(self doSignalSemaphoreWithIndex: i) ifTrue:
  [switched := true].
  externalSemaphoreSignalResponses at: i put: (responses := responses + 1)]].
  ^switched!

Item was changed:
  ----- Method: CogVMSimulator>>initialize (in category 'initialization') -----
  initialize
  "Initialize the CogVMSimulator when running the interpreter inside Smalltalk.  The
  primary responsibility of this method is to allocate Smalltalk Arrays for variables
  that will be declared as statically-allocated global arrays in the translated code."
  super initialize.
 
  transcript := Transcript.
 
  objectMemory ifNil:
  [objectMemory := self class objectMemoryClass simulatorClass new].
  cogit ifNil:
  [cogit := self class cogitClass new setInterpreter: self].
  objectMemory coInterpreter: self cogit: cogit.
 
  cogit numRegArgs > 0 ifTrue:
  [debugStackDepthDictionary := Dictionary new].
 
  cogThreadManager ifNotNil:
  [super initialize].
 
  self assert: ConstMinusOne = (objectMemory integerObjectOf: -1).
 
  cogMethodZone := cogit methodZone. "Because Slang can't remove intermediate implicit receivers (cogit methodZone foo doesn't reduce to foo())"
  enableCog := true.
 
  methodCache := Array new: MethodCacheSize.
  nsMethodCache := Array new: NSMethodCacheSize.
  atCache := nil.
  self flushMethodCache.
  cogCompiledCodeCompactionCalledFor := false.
  gcSemaphoreIndex := 0.
  externalSemaphoreSignalRequests := externalSemaphoreSignalResponses := #().
  externalPrimitiveTable := CArrayAccessor on: (Array new: MaxExternalPrimitiveTableSize).
  externalPrimitiveTableFirstFreeIndex := 0.
  primitiveTable := self class primitiveTable copy.
  mappedPluginEntries := OrderedCollection new.
  objectMemory hasSpurMemoryManagerAPI
  ifTrue:
  [primitiveAccessorDepthTable := Array new: primitiveTable size.
  pluginList := {}.
  self loadNewPlugin: '']
  ifFalse:
  [pluginList := {'' -> self }].
  desiredNumStackPages := desiredEdenBytes := desiredCogCodeSize := 0.
  "This is initialized on loading the image, but convenient for testing stack page values..."
  numStackPages := self defaultNumStackPages.
+ startMicroseconds := lastYieldMicroseconds := self ioUTCStartMicroseconds.
- startMicroseconds := self ioUTCStartMicroseconds.
  maxLiteralCountForCompile := MaxLiteralCountForCompile.
  minBackwardJumpCountForCompile := MinBackwardJumpCountForCompile.
  flagInterpretedMethods := false.
 
  "initialize InterpreterSimulator variables used for debugging"
  byteCount := lastPollCount := sendCount := lookupCount := 0.
  quitBlock := [^self close].
  traceOn := true.
  printSends := printFrameAtEachStep := printBytecodeAtEachStep := false.
  myBitBlt := BitBltSimulator new setInterpreter: self.
  displayForm := fakeForm := 'Display has not yet been installed' asDisplayText form.
  eventQueue := SharedQueue new.
  suppressHeartbeatFlag := deferSmash := deferredSmash := false.
  systemAttributes := Dictionary new.
  primTraceLog := CArrayAccessor on: (Array new: 256 withAll: 0).
  primTraceLogIndex := 0.
  traceLog := CArrayAccessor on: (Array new: TraceBufferSize withAll: 0).
  traceLogIndex := 0.
  traceSources := TraceSources.
  statCodeCompactionCount := 0.
  statCodeCompactionUsecs := 0.
  extSemTabSize := 256!

Item was changed:
  ----- Method: Integer>>asCharPtr (in category '*VMMaker-interpreter simulator') -----
  asCharPtr
  ^(Notification new tag: #getSimulator; signal)
+ ifNotNil: [:simulator| | interpreter |
+ interpreter := simulator getInterpreter.
+ (interpreter firstIndexableField: self) asInteger
+ coerceTo: #'char *'
+ sim: interpreter]
- ifNotNil: [:simulator| self coerceTo: #'char *' sim: simulator getInterpreter]
  ifNil: [self]!

Item was added:
+ ----- Method: InterpreterPlugin>>close (in category 'simulation support') -----
+ close
+ "Simulation subclasses needing some specific close action override as required."
+ <doNotGenerate>!

Item was changed:
  StackInterpreterPrimitives subclass: #StackInterpreterSimulator
+ instanceVariableNames: 'parent bootstrapping byteCount breakCount sendCount lookupCount printSends printReturns traceOn myBitBlt displayForm fakeForm filesOpen imageName pluginList mappedPluginEntries quitBlock transcript displayView eventTransformer printFrameAtEachStep printBytecodeAtEachStep systemAttributes startMicroseconds lastYieldMicroseconds externalSemaphoreSignalRequests externalSemaphoreSignalResponses extSemTabSize atEachStepBlock disableBooleanCheat performFilters eventQueue assertVEPAES'
- instanceVariableNames: 'parent bootstrapping byteCount breakCount sendCount lookupCount printSends printReturns traceOn myBitBlt displayForm fakeForm filesOpen imageName pluginList mappedPluginEntries quitBlock transcript displayView eventTransformer printFrameAtEachStep printBytecodeAtEachStep systemAttributes startMicroseconds externalSemaphoreSignalRequests externalSemaphoreSignalResponses extSemTabSize atEachStepBlock disableBooleanCheat performFilters eventQueue assertVEPAES'
  classVariableNames: ''
  poolDictionaries: ''
  category: 'VMMaker-InterpreterSimulation'!
 
  !StackInterpreterSimulator commentStamp: 'eem 9/3/2013 11:05' prior: 0!
  This class defines basic memory access and primitive simulation so that the StackInterpreter can run simulated in the Squeak environment.  It also defines a number of handy object viewing methods to facilitate pawing around in the object memory.
 
  To see the thing actually run, you could (after backing up this image and changes), execute
 
  (StackInterpreterSimulator new openOn: Smalltalk imageName) test
 
  ((StackInterpreterSimulator newWithOptions: #(NewspeakVM true MULTIPLEBYTECODESETS true))
  openOn: 'ns101.image') test
 
  and be patient both to wait for things to happen, and to accept various things that may go wrong depending on how large or unusual your image may be.  We usually do this with a small and simple benchmark image.
 
  Here's an example of what Eliot uses to launch the simulator in a window.  The bottom-right window has a menu packed with useful stuff:
 
  | vm |
  vm := StackInterpreterSimulator newWithOptions: #().
  vm openOn: '/Users/eliot/Squeak/Squeak4.4/trunk44.image'.
  vm setBreakSelector: #&.
  vm openAsMorph; run!

Item was changed:
  ----- Method: StackInterpreterSimulator>>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]]!
- pluginList do: [:plugin| (plugin ~~ self and: [plugin respondsTo: #close]) ifTrue: [plugin close]]!

Item was changed:
  ----- Method: StackInterpreterSimulator>>doSignalExternalSemaphores: (in category 'process primitive support') -----
  doSignalExternalSemaphores: minTableSize
  "This is a non-thread-safe simulation.  See platforms/Cross/vm/sqExternalSemaphores.c
+ for the real code.  For the benefit of the SocketPluginSimulator, do a yield every 100
+ virtual microseconds."
+ | now switched |
+ now := self ioUTCMicroseconds.
+ now - lastYieldMicroseconds >= 100 ifTrue:
+ [lastYieldMicroseconds := now.
+ Processor yield].
+
- for the real code."
- | switched |
  switched := false.
  1 to: (minTableSize min: externalSemaphoreSignalRequests size) do:
  [:i| | responses |
  responses := externalSemaphoreSignalResponses at: i.
  [responses < (externalSemaphoreSignalRequests at: i)] whileTrue:
  [(self doSignalSemaphoreWithIndex: i) ifTrue:
  [switched := true].
  externalSemaphoreSignalResponses at: i put: (responses := responses + 1)]].
  ^switched!

Item was changed:
  ----- Method: StackInterpreterSimulator>>initialize (in category 'initialization') -----
  initialize
  "Initialize the StackInterpreterSimulator when running the interpreter
  inside Smalltalk. The primary responsibility of this method is to allocate
  Smalltalk Arrays for variables that will be declared as statically-allocated
  global arrays in the translated code."
  super initialize.
 
  bootstrapping := false.
  transcript := Transcript.
 
  objectMemory ifNil:
  [objectMemory := self class objectMemoryClass simulatorClass new].
  objectMemory coInterpreter: self.
 
  self assert: ConstMinusOne = (objectMemory integerObjectOf: -1).
 
  methodCache := Array new: MethodCacheSize.
  nsMethodCache := Array new: NSMethodCacheSize.
  atCache := Array new: AtCacheTotalSize.
  self flushMethodCache.
  gcSemaphoreIndex := 0.
  externalSemaphoreSignalRequests := externalSemaphoreSignalResponses := #().
  externalPrimitiveTable := CArrayAccessor on: (Array new: MaxExternalPrimitiveTableSize).
  externalPrimitiveTableFirstFreeIndex := 0.
  primitiveTable := self class primitiveTable copy.
  mappedPluginEntries := OrderedCollection new.
  objectMemory hasSpurMemoryManagerAPI
  ifTrue:
  [primitiveAccessorDepthTable := Array new: primitiveTable size.
  pluginList := {}.
  self loadNewPlugin: '']
  ifFalse:
  [pluginList := {'' -> self }].
  desiredNumStackPages := desiredEdenBytes := 0.
  "This is initialized on loading the image, but convenient for testing stack page values..."
  numStackPages := self defaultNumStackPages.
+ startMicroseconds := lastYieldMicroseconds := self ioUTCStartMicroseconds.
- startMicroseconds := self ioUTCStartMicroseconds.
 
  "initialize InterpreterSimulator variables used for debugging"
  byteCount := sendCount := lookupCount := 0.
  quitBlock := [^self close].
  traceOn := true.
  printSends := printReturns := printFrameAtEachStep := printBytecodeAtEachStep := false.
  myBitBlt := BitBltSimulator new setInterpreter: self.
  displayForm := fakeForm := 'Display has not yet been installed' asDisplayText form.
  eventQueue := SharedQueue new.
  suppressHeartbeatFlag := false.
  systemAttributes := Dictionary new.
  extSemTabSize := 256.
  disableBooleanCheat := false.
  assertVEPAES := true. "a flag so the assertValidExecutionPointers can be disabled for simulation speed"!

Item was added:
+ ----- Method: StackInterpreterSimulator>>windowIsClosing (in category 'primitive support') -----
+ windowIsClosing
+ quitBlock ifNotNil:
+ [:effectiveQuitBlock|
+ quitBlock := nil. "stop recursion on explicit window close."
+ [effectiveQuitBlock value]
+ on: BlockCannotReturn
+ do: [:ex|]] "Cause return from #test, et al"!