Eliot Miranda uploaded a new version of VMMaker to project VM Maker: http://source.squeak.org/VMMaker/VMMaker.oscog-eem.2963.mcz ==================== Summary ==================== Name: VMMaker.oscog-eem.2963 Author: eem Time: 27 May 2021, 10:26:40.297558 am UUID: efbaae14-a74e-4d2f-a882-21c3b80d3a9f Ancestors: VMMaker.oscog-eem.2962 Get StackInterpreterSimulator respond to input in a timely manner. Eliminate a few gratuitous changes between CogVMSimulator and StackInterpreterSimulator. =============== Diff against VMMaker.oscog-eem.2962 =============== Item was changed: ----- Method: CogVMSimulator>>allObjectsSelect: (in category 'debug support') ----- allObjectsSelect: objBlock "self allObjectsSelect: [:oop | (self baseHeader: oop) = 1234]" | selected | selected := OrderedCollection new. objectMemory allObjectsDoSafely: + [:obj| + (objBlock value: obj) ifTrue: [selected addLast: obj]]. + ^selected! - [:oop| (objBlock value: oop) ifTrue: [selected addLast: oop]]. - ^ selected! Item was changed: ----- Method: CogVMSimulator>>ioUTCMicroseconds (in category 'I/O primitives support') ----- ioUTCMicroseconds "Return the value of the microsecond clock." "NOT. Actually, we want something a lot slower and, for exact debugging, something more repeatable than real time. Dan had an idea: use the byteCount... We increment byteCount in stackLimitFromMachineCode and a real machine can easily run e.g. nfib at 6e7 / second, which this would be 1 usec ~= 60 byteCounts. + Use 100 byteCounts per usec by default; see CogVMSimulator class>>initializeWithOptions:" - Use 10 byteCounts per usec by default; see CogVMSimulator class>>initializeWithOptions:objectMemoryClass:" ^byteCount // ByteCountsPerMicrosecond + startMicroseconds "Dan: At 20k bytecodes per second, this gives us about 200 ticks per second, or about 1/5 of what you'd expect for the real time clock. This should still service events at one or two per second"! Item was changed: ----- Method: CogVMSimulator>>openOn:extraMemory: (in category 'initialize-release') ----- openOn: fileName extraMemory: extraBytes "CogVMSimulator new openOn: 'clone.im' extraMemory: 100000" | f version headerSize dataSize count oldBaseAddr bytesToShift swapBytes headerFlags firstSegSize heapSize hdrNumStackPages hdrEdenBytes hdrMaxExtSemTabSize hdrCogCodeSize stackZoneSize methodCacheSize primTraceLogSize allocationReserve | "open image file and read the header" (f := self openImageFileNamed: fileName) ifNil: [^self]. "Set the image name and the first argument; there are no arguments during simulation unless set explicitly." systemAttributes at: 1 put: fileName. ["begin ensure block..." imageName := f fullName. f binary. version := self getWord32FromFile: f swap: false. "current version: 16r1968 (=6504) vive la revolucion!!" (self readableFormat: version) ifTrue: [swapBytes := false] ifFalse: [(version := version byteSwap32) = self imageFormatVersion ifTrue: [swapBytes := true] ifFalse: [self error: 'incomaptible image format']]. headerSize := self getWord32FromFile: f swap: swapBytes. dataSize := self getLongFromFile: f swap: swapBytes. "length of heap in file" oldBaseAddr := self getLongFromFile: f swap: swapBytes. "object memory base address of image" objectMemory specialObjectsOop: (self getLongFromFile: f swap: swapBytes). objectMemory lastHash: (self getLongFromFile: f swap: swapBytes). "Should be loaded from, and saved to the image header" savedWindowSize := self getLongFromFile: f swap: swapBytes. headerFlags := self getLongFromFile: f swap: swapBytes. self setImageHeaderFlagsFrom: headerFlags. extraVMMemory := self getWord32FromFile: f swap: swapBytes. hdrNumStackPages := self getShortFromFile: f swap: swapBytes. "4 stack pages is small. Should be able to run with as few as three. 4 should be comfortable but slow. 8 is a reasonable default. Can be changed via vmParameterAt: 43 put: n" numStackPages := desiredNumStackPages ~= 0 ifTrue: [desiredNumStackPages] ifFalse: [hdrNumStackPages = 0 ifTrue: [self defaultNumStackPages] ifFalse: [hdrNumStackPages]]. desiredNumStackPages := hdrNumStackPages. stackZoneSize := self computeStackZoneSize. "This slot holds the size of the native method zone in 1k units. (pad to word boundary)." hdrCogCodeSize := (self getShortFromFile: f swap: swapBytes) * 1024. cogCodeSize := desiredCogCodeSize ~= 0 ifTrue: [desiredCogCodeSize] ifFalse: [hdrCogCodeSize = 0 ifTrue: [cogit defaultCogCodeSize] ifFalse: [hdrCogCodeSize]]. desiredCogCodeSize := hdrCogCodeSize. self assert: f position = (objectMemory wordSize = 4 ifTrue: [40] ifFalse: [64]). hdrEdenBytes := self getWord32FromFile: f swap: swapBytes. objectMemory edenBytes: (desiredEdenBytes ~= 0 ifTrue: [desiredEdenBytes] ifFalse: [hdrEdenBytes = 0 ifTrue: [objectMemory defaultEdenBytes] ifFalse: [hdrEdenBytes]]). desiredEdenBytes := hdrEdenBytes. hdrMaxExtSemTabSize := self getShortFromFile: f swap: swapBytes. hdrMaxExtSemTabSize ~= 0 ifTrue: [self setMaxExtSemSizeTo: hdrMaxExtSemTabSize]. "pad to word boundary. This slot can be used for anything else that will fit in 16 bits. Preserve it to be polite to other VMs." the2ndUnknownShort := self getShortFromFile: f swap: swapBytes. self assert: f position = (objectMemory wordSize = 4 ifTrue: [48] ifFalse: [72]). firstSegSize := self getLongFromFile: f swap: swapBytes. objectMemory firstSegmentSize: firstSegSize. "For Open PICs to be able to probe the method cache during simulation the methodCache must be relocated to memory." methodCacheSize := methodCache size * objectMemory wordSize. primTraceLogSize := primTraceLog size * objectMemory wordSize. "To cope with modern OSs that disallow executing code in writable memory we dual-map the code zone, one mapping with read/write permissions and the other with read/execute permissions. In simulation all we can do is use memory, so if we're simulating dual mapping we use double the memory and simulate the memory sharing in the Cogit's backEnd." effectiveCogCodeSize := (InitializationOptions at: #DUAL_MAPPED_CODE_ZONE ifAbsent: [false]) ifTrue: [cogCodeSize * 2] ifFalse: [cogCodeSize]. "allocate interpreter memory. This list is in address order, low to high. In the actual VM the stack zone exists on the C stack." heapBase := (Cogit guardPageSize + effectiveCogCodeSize + stackZoneSize + methodCacheSize + primTraceLogSize + self rumpCStackSize) roundUpTo: objectMemory allocationUnit. "compare memory requirements with availability" allocationReserve := self interpreterAllocationReserveBytes. objectMemory hasSpurMemoryManagerAPI ifTrue: [| freeOldSpaceInImage headroom | freeOldSpaceInImage := self getLongFromFile: f swap: swapBytes. headroom := objectMemory initialHeadroom: extraVMMemory givenFreeOldSpaceInImage: freeOldSpaceInImage. heapSize := objectMemory roundUpHeapSize: dataSize + headroom + objectMemory newSpaceBytes + (headroom > allocationReserve ifTrue: [0] ifFalse: [allocationReserve])] ifFalse: [heapSize := dataSize + extraBytes + objectMemory newSpaceBytes + (extraBytes > allocationReserve ifTrue: [0] ifFalse: [allocationReserve])]. + "allocate interpreter memory" + heapBase := objectMemory startOfMemory. + objectMemory + setHeapBase: heapBase + memoryLimit: heapBase + heapSize + endOfMemory: heapBase + dataSize. "bogus for Spur" - heapBase := objectMemory - setHeapBase: heapBase - memoryLimit: heapBase + heapSize - endOfMemory: heapBase + dataSize. self assert: cogCodeSize \\ 4 = 0. self assert: objectMemory memoryLimit \\ 4 = 0. self assert: self rumpCStackSize \\ 4 = 0. objectMemory allocateMemoryOfSize: objectMemory memoryLimit. "read in the image in bulk, then swap the bytes if necessary" f position: headerSize. count := objectMemory readHeapFromImageFile: f dataBytes: dataSize. count ~= dataSize ifTrue: [self halt]] ensure: [f close]. self moveMethodCacheToMemoryAt: objectMemory cogCodeBase + effectiveCogCodeSize + stackZoneSize. self movePrimTraceLogToMemoryAt: objectMemory cogCodeBase + effectiveCogCodeSize + stackZoneSize + methodCacheSize. self ensureImageFormatIsUpToDate: swapBytes. bytesToShift := objectMemory memoryBaseForImageRead - oldBaseAddr. "adjust pointers for zero base address" UIManager default informUser: 'Relocating object pointers...' during: [self initializeInterpreter: bytesToShift]. self initializeCodeGenerator! 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 primTraceLog breakBlock inputSemaphoreIndex' + classVariableNames: 'ByteCountsPerMicrosecond' - 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 added: + ----- Method: StackInterpreterSimulator class>>initializeWithOptions: (in category 'class initialization') ----- + initializeWithOptions: optionsDictionary + super initializeWithOptions: optionsDictionary. + + ByteCountsPerMicrosecond := InitializationOptions + at: #ByteCountsPerMicrosecond + ifAbsent: [50]! Item was changed: ----- Method: StackInterpreterSimulator>>incrementByteCount (in category 'interpreter shell') ----- incrementByteCount (byteCount := byteCount + 1) = breakCount ifTrue: + [self doOrDefer: [self changed: #byteCountText; changed: #composeAll]. - [self doOrDefer: [self changed: #byteCountText]. self halt: 'breakCount reached']. byteCount \\ 1000 = 0 ifTrue: + [self doOrDefer: [self changed: #byteCountText; changed: #composeAll]. - [self doOrDefer: [self changed: #byteCountText]. self forceInterruptCheck]! Item was changed: ----- Method: StackInterpreterSimulator>>ioRelinquishProcessorForMicroseconds: (in category 'I/O primitives support') ----- ioRelinquishProcessorForMicroseconds: microseconds "In the simulator give an indication that we're idling and check for input. If there's an input event, fail to give the system a chance to respond to it in a timely manner." Display reverse: ((displayView ifNil: [0@0] ifNotNil: [displayView bounds origin]) extent: 16@16). Processor activeProcess == Project uiProcess ifTrue: [World doOneCycle]. (stackLimit = self allOnesAsCharStar and: [nextPollUsecs <= self ioUTCMicroseconds]) ifTrue: ["Not only do we need to fail, we also need to push time faster since the damn Morphic eventTickler process waits on a delay." "ioUTCMicroseconds" + byteCount := byteCount + (1000 * ByteCountsPerMicrosecond). - byteCount := byteCount + (1000 * 50). self primitiveFail] ifFalse: [microseconds >= 1000 ifTrue: [stackLimit = self allOnesAsCharStar ifFalse: + [(Delay forMilliseconds: microseconds + 999 // 1000) wait. + self forceInterruptCheck]] - [(Delay forMilliseconds: microseconds + 999 // 1000) wait]] ifFalse: [Processor yield]]. "And increase the byteCount form which the microsecond clock is derived..." + byteCount := byteCount + (microseconds * ByteCountsPerMicrosecond) - 1. - byteCount := byteCount + microseconds - 1. self incrementByteCount! Item was changed: ----- Method: StackInterpreterSimulator>>ioUTCMicroseconds (in category 'I/O primitives support') ----- ioUTCMicroseconds "Return the value of the microsecond clock." "NOT. Actually, we want something a lot slower and, for exact debugging, + something more repeatable than real time. Dan had an idea: use the byteCount... + Use 50 byteCounts per usec by default; see StackInterpreterSimulator class>>initializeWithOptions:" - something more repeatable than real time. Dan had an idea: use the byteCount..." + ^byteCount // ByteCountsPerMicrosecond + startMicroseconds + + "Dan: + At 20k bytecodes per second, this gives us about 200 ticks per second, or about 1/5 + of what you'd expect for the real time clock. This should still service events at one or + two per second"! - ^(byteCount // 50) + startMicroseconds! Item was changed: ----- Method: StackInterpreterSimulator>>openOn:extraMemory: (in category 'initialize-release') ----- openOn: fileName extraMemory: extraBytes "StackInterpreterSimulator new openOn: 'clone.im' extraMemory: 100000" | f version headerSize dataSize count oldBaseAddr bytesToShift swapBytes headerFlags heapBase firstSegSize heapSize hdrNumStackPages hdrEdenBytes hdrMaxExtSemTabSize allocationReserve | "open image file and read the header" (f := self openImageFileNamed: fileName) ifNil: [^self]. "Set the image name and the first argument; there are no arguments during simulation unless set explicitly." systemAttributes at: 1 put: fileName. ["begin ensure block..." imageName := f fullName. f binary. version := self getWord32FromFile: f swap: false. "current version: 16r1968 (=6504) vive la revolucion!!" (self readableFormat: version) ifTrue: [swapBytes := false] + ifFalse: [(version := version byteSwap32) = self imageFormatVersion - ifFalse: [(version := objectMemory byteSwapped: version) = self imageFormatVersion ifTrue: [swapBytes := true] ifFalse: [self error: 'incomaptible image format']]. headerSize := self getWord32FromFile: f swap: swapBytes. dataSize := self getLongFromFile: f swap: swapBytes. "length of heap in file" oldBaseAddr := self getLongFromFile: f swap: swapBytes. "object memory base address of image" objectMemory specialObjectsOop: (self getLongFromFile: f swap: swapBytes). objectMemory lastHash: (self getLongFromFile: f swap: swapBytes). "Should be loaded from, and saved to the image header" savedWindowSize := self getLongFromFile: f swap: swapBytes. headerFlags := self getLongFromFile: f swap: swapBytes. self setImageHeaderFlagsFrom: headerFlags. extraVMMemory := self getWord32FromFile: f swap: swapBytes. hdrNumStackPages := self getShortFromFile: f swap: swapBytes. "4 stack pages is small. Should be able to run with as few as three. 4 should be comfortable but slow. 8 is a reasonable default. Can be changed via vmParameterAt: 43 put: n" numStackPages := desiredNumStackPages ~= 0 ifTrue: [desiredNumStackPages] ifFalse: [hdrNumStackPages = 0 ifTrue: [self defaultNumStackPages] ifFalse: [hdrNumStackPages]]. desiredNumStackPages := hdrNumStackPages. "pad to word boundary. This slot can be used for anything else that will fit in 16 bits. It is used for the cog code size in Cog. Preserve it to be polite to other VMs." theUnknownShort := self getShortFromFile: f swap: swapBytes. self assert: f position = (objectMemory wordSize = 4 ifTrue: [40] ifFalse: [64]). hdrEdenBytes := self getWord32FromFile: f swap: swapBytes. objectMemory edenBytes: (hdrEdenBytes = 0 ifTrue: [objectMemory defaultEdenBytes] ifFalse: [hdrEdenBytes]). desiredEdenBytes := hdrEdenBytes. hdrMaxExtSemTabSize := self getShortFromFile: f swap: swapBytes. hdrMaxExtSemTabSize ~= 0 ifTrue: [self setMaxExtSemSizeTo: hdrMaxExtSemTabSize]. "pad to word boundary. This slot can be used for anything else that will fit in 16 bits. Preserve it to be polite to other VMs." the2ndUnknownShort := self getShortFromFile: f swap: swapBytes. self assert: f position = (objectMemory wordSize = 4 ifTrue: [48] ifFalse: [72]). firstSegSize := self getLongFromFile: f swap: swapBytes. objectMemory firstSegmentSize: firstSegSize. "compare memory requirements with availability" allocationReserve := self interpreterAllocationReserveBytes. objectMemory hasSpurMemoryManagerAPI ifTrue: [| freeOldSpaceInImage headroom | freeOldSpaceInImage := self getLongFromFile: f swap: swapBytes. headroom := objectMemory initialHeadroom: extraVMMemory givenFreeOldSpaceInImage: freeOldSpaceInImage. heapSize := objectMemory roundUpHeapSize: dataSize + headroom + objectMemory newSpaceBytes + (headroom > allocationReserve ifTrue: [0] ifFalse: [allocationReserve])] ifFalse: [heapSize := dataSize + extraBytes + objectMemory newSpaceBytes + (extraBytes > allocationReserve ifTrue: [0] ifFalse: [allocationReserve])]. "allocate interpreter memory" heapBase := objectMemory startOfMemory. objectMemory setHeapBase: heapBase memoryLimit: heapBase + heapSize endOfMemory: heapBase + dataSize. "bogus for Spur" objectMemory allocateMemoryOfSize: objectMemory memoryLimit. "read in the image in bulk, then swap the bytes if necessary" f position: headerSize. count := objectMemory readHeapFromImageFile: f dataBytes: dataSize. count ~= dataSize ifTrue: [self halt]] ensure: [f close]. self ensureImageFormatIsUpToDate: swapBytes. bytesToShift := objectMemory memoryBaseForImageRead - oldBaseAddr. "adjust pointers for zero base address" UIManager default informUser: 'Relocating object pointers...' during: [self initializeInterpreter: bytesToShift]! Item was changed: ----- Method: StackInterpreterSimulator>>parent (in category 'accessing') ----- parent - ^ parent! |
Free forum by Nabble | Edit this page |