[Vm-dev] VM Maker: VMMaker.oscog-eem.2319.mcz

commits at source.squeak.org commits at source.squeak.org
Thu Jan 18 05:37:32 UTC 2018


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

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

Name: VMMaker.oscog-eem.2319
Author: eem
Time: 17 January 2018, 9:37:07.372314 pm
UUID: fbf82405-54b5-46c9-8488-35a69ddb40da
Ancestors: VMMaker.oscog-eem.2318

Simulation:
Close files properly in the FilePliginSimulator and recycle file handle indices.

Comma separate the bytecode count text for legibility.

Update the VM window title on Snapshot.

Use Project current restore to allow the GUI to update instead of being Morphic-specifc (thanks Bert).

Provide a VM option to turn off stack depth checking (since non-local returns occasionally violate stack depth and that can halt a long run).

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

Item was changed:
  ----- Method: CogVMSimulator>>byteCountText (in category 'UI') -----
  byteCountText
+ 	^(String streamContents: [:s| s nextPutAll: byteCount asStringWithCommas; nextPut: $/; nextPutAll: sendCount asStringWithCommas]) asText!
- 	^(String streamContents: [:s| s print: byteCount; nextPut: $/; print: sendCount]) asText!

Item was changed:
  ----- Method: CogVMSimulator>>imageNamePut:Length: (in category 'file primitives') -----
  imageNamePut: p Length: sz
+ 	| newName window |
- 	| newName |
  	newName := ByteString new: sz.
  	1 to: sz  do:
  		[:i |
  		newName
  			at: i
  			put: (Character value: (objectMemory byteAt: p + i - 1))].
+ 	imageName := newName.
+ 	(displayView notNil
+ 	 and: [(window := displayView containingWindow) notNil]) ifTrue:
+ 		[window setLabel: (window label
+ 							copyReplaceFrom: (window label lastIndexOf: Character space) + 1
+ 							to: window label size
+ 							with: (FileDirectory localNameFor: imageName))]!
- 	imageName := newName!

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
+ 	 and: [VMClass initializationOptions at: #CheckStackDepth ifAbsent: [true]]) ifTrue:
- 	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.
  	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: CogVMSimulator>>stackLimitFromMachineCode (in category 'I/O primitives support') -----
  stackLimitFromMachineCode
  	"Intercept accesses to the stackLimit from machine code to increment byteCount so that
  	 ioMSecs/ioMicroseconds does something reasonable when we're purely in machine code.
  	 Force an interrupt check every 2 ms in simulated time (2ms = the default heartbeat), or if
  	 the profile tick has expired.."
  
  	(byteCount := byteCount + 1) - lastPollCount >= (2000 * ByteCountsPerMicrosecond) ifTrue:
+ 		[lastPollCount := byteCount.
+ 		 self doOrDefer: [self changed: #byteCountText; changed: #composeAll]].
- 		[lastPollCount := byteCount].
  	(lastPollCount = byteCount
  	 or: [nextProfileTick > 0 and: [nextProfileTick <= self ioUTCMicroseconds]]) ifTrue:
  		[suppressHeartbeatFlag "gets set by selector breakpoints"
  			ifTrue: [self forceInterruptCheck]
  			ifFalse: [self forceInterruptCheckFromHeartbeat]].
  	^stackLimit!

Item was changed:
  ----- Method: FilePluginSimulator>>fileOpenName:size:write:secure: (in category 'file primitives') -----
  fileOpenName: nameIndex size: nameSize write: writeFlag secure: secureFlag
  	"Open the named file, possibly checking security. Answer the file oop."
  	| path f index |
  	openFiles size >= maxOpenFiles ifTrue:
  		[^interpreterProxy primitiveFailFor: PrimErrLimitExceeded].
  	path := interpreterProxy asString: nameIndex size: nameSize.
  	f := writeFlag
  			ifTrue: [FileStream fileNamed: path]
  			ifFalse:
  				[(StandardFileStream isAFileNamed: path) ifTrue:
  					[FileStream readOnlyFileNamed: path]].
  	f ifNil: [^interpreterProxy primitiveFail].
  	f binary.
+ 	index := (3 to: openFiles size + 1) detect: [:n| (openFiles includesKey: n) not].
- 	index := openFiles size + 1.
  	openFiles at: index put: f.
  	^interpreterProxy integerObjectOf: index!

Item was changed:
  ----- Method: FilePluginSimulator>>fileOpenNewName:size:secure: (in category 'file primitives') -----
  fileOpenNewName: nameIndex size: nameSize secure: secureFlag
  	"Open the new named file, possibly checking security. Answer the file oop."
  	| path f index |
  	openFiles size >= maxOpenFiles ifTrue:
  		[^interpreterProxy primitiveFailFor: PrimErrLimitExceeded].
  	path := interpreterProxy interpreter asString: nameIndex size: nameSize.
  	"the #defaultAction for FileExistsException creates a dialog,
  	so it is caught and resignaled as a generic Error"
  	[f := FileStream newFileNamed: nameIndex]
  		on: FileExistsException
  		do: [:error | ^ interpreterProxy primitiveFailFor: PrimErrInappropriate].
  	f ifNil: [^interpreterProxy primitiveFail].
  	f binary.
+ 	index := (3 to: openFiles size + 1) detect: [:n| (openFiles includesKey: n) not].
- 	index := openFiles size + 1.
  	openFiles at: index put: f.
  	^interpreterProxy integerObjectOf: index!

Item was changed:
  ----- Method: FilePluginSimulator>>sqFileClose: (in category 'simulation') -----
  sqFileClose: file
+ 	| index |
+ 	index := openFiles keyAtValue: file.
+ 	openFiles removeKey: index.
+ 	states removeKey: file ifAbsent: [].
+ 	file close!
- 	file close.
- 	self recordStateOf: file!

Item was changed:
  ----- Method: StackInterpreter>>ioForceDisplayUpdate (in category 'simulation') -----
  ioForceDisplayUpdate
  	"Make sure the display is updated.  Simulation only"
  	<doNotGenerate>
+ 	Project current restore!
- 	World displayWorldSafely!

Item was changed:
  ----- Method: StackInterpreterSimulator>>byteCountText (in category 'UI') -----
  byteCountText
+ 	^ byteCount asStringWithCommas asText!
- 	^ byteCount printString asText!

Item was changed:
  ----- Method: StackInterpreterSimulator>>imageNamePut:Length: (in category 'file primitives') -----
  imageNamePut: p Length: sz
+ 	| newName window |
- 	| newName |
  	newName := ByteString new: sz.
  	1 to: sz  do:
  		[:i |
  		newName
  			at: i
  			put: (Character value: (objectMemory byteAt: p + i - 1))].
+ 	imageName := newName.
+ 	(displayView notNil
+ 	 and: [(window := displayView containingWindow) notNil]) ifTrue:
+ 		[window setLabel: (window label
+ 							copyReplaceFrom: (window label lastIndexOf: Character space) + 1
+ 							to: window label size
+ 							with: (FileDirectory localNameFor: imageName))]!
- 	imageName := newName!



More information about the Vm-dev mailing list