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

commits at source.squeak.org commits at source.squeak.org
Mon Jan 25 02:15:53 UTC 2016


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

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

Name: VMMaker.oscog-eem.1667
Author: eem
Time: 25 January 2016, 6:14:12.220089 pm
UUID: bcfe6ade-2dce-4747-99d8-cc28480a226e
Ancestors: VMMaker.oscog-eem.1666

General: Add vmParameter 20 (stolen from ikp's JITTER, forgive me Ian) to answer the utc microseconds at startup.

Slang: Fix exitVar:label: given the change in VMMaker.oscog-eem.1665 to eliding empty inlines.

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

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 := self ioUTCStartMicroseconds.
- 	startMicroseconds := Time totalSeconds * 1000000.
  	maxLiteralCountForCompile := MaxLiteralCountForCompile.
  	minBackwardJumpCountForCompile := MinBackwardJumpCountForCompile.
  	flagInterpretedMethods := false.
  
  	"initialize InterpreterSimulator variables used for debugging"
  	byteCount := lastPollCount := sendCount := lookupCount := 0.
  	quitBlock := [^ self].
  	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 added:
+ ----- Method: CogVMSimulator>>ioUTCStartMicroseconds (in category 'I/O primitives support') -----
+ ioUTCStartMicroseconds
+ 	"Answer the value of the microsecond clock at startup."
+ 
+ 	^startMicroseconds ifNil:
+ 		[self class initializationOptions
+ 			at: #startMicroseconds
+ 			ifAbsent: [[Time utcMicrosecondClock] on: Error do: [Time totalSeconds * 1000000]]]!

Item was changed:
  ----- Method: StackInterpreterPrimitives>>primitiveVMParameter (in category 'system control primitives') -----
(excessive size, no diff calculated)

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 := self ioUTCStartMicroseconds.
- 	startMicroseconds := Time totalSeconds * 1000000.
  
  	"initialize InterpreterSimulator variables used for debugging"
  	byteCount := sendCount := lookupCount := 0.
  	quitBlock := [^self].
  	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>>ioUTCStartMicroseconds (in category 'I/O primitives support') -----
+ ioUTCStartMicroseconds
+ 	"Answer the value of the microsecond clock at startup."
+ 
+ 	^startMicroseconds ifNil:
+ 		[self class initializationOptions
+ 			at: #startMicroseconds
+ 			ifAbsent: [[Time utcMicrosecondClock] on: Error do: [Time totalSeconds * 1000000]]]!

Item was changed:
  ----- Method: TMethod>>exitVar:label: (in category 'inlining') -----
  exitVar: exitVar label: exitLabel
  	"Replace each return statement in this method with an assignment to the
  	 exit variable followed by either a return or a goto to the given label.
  	 Answer if a goto was generated."
  	"Optimization: If exitVar is nil, the return value of the inlined method is not being used, so don't add the assignment statement."
  
  	| labelUsed map eliminateReturnSelfs |
  	labelUsed := false.
  	map := Dictionary new.
  	"Conceivably one might ^self from a struct class and mean it.  In most cases though
  	 ^self means `get me outta here, fast'.  So unless this method is from a VMStruct class,
  	 elide any ^self's"
  	eliminateReturnSelfs := ((definingClass inheritsFrom: VMClass) and: [definingClass isStructClass]) not
  							  and: [returnType = #void or: [returnType = #sqInt]].
  	parseTree nodesDo:
  		[:node | | replacement |
  		node isReturn ifTrue:
  			[replacement := (node expression isVariable "Eliminate ^self's"
  							   and: [node expression name = 'self'
  							   and: [eliminateReturnSelfs]])
  								ifTrue: [nil]
  								ifFalse:
  									[exitVar
  										ifNil: [node expression]
  										ifNotNil: [TAssignmentNode new
  													setVariable: (TVariableNode new setName: exitVar)
  													expression: node expression]].
  			 node ~~ parseTree statements last ifTrue:
  				[replacement := replacement
  									ifNil: [TGoToNode new setLabel: exitLabel; yourself]
  									ifNotNil:
  										[TStmtListNode new
  											setArguments: #()
  											statements: {replacement.
  														  TGoToNode new setLabel: exitLabel; yourself};
  											yourself].
  				 labelUsed := true].
  			map
  				at: node
  				put: (replacement ifNil:
  						[TLabeledCommentNode new setComment: 'return ', node expression printString])]].
  	parseTree replaceNodesIn: map.
  	"Now flatten any new statement lists..."
  	parseTree nodesDo:
  		[:node| | list |
+ 		(node isStmtList
+ 		 and: [node statements notEmpty
+ 		 and: [node statements last isStmtList]]) ifTrue:
- 		(node isStmtList and: [node statements last isStmtList]) ifTrue:
  			[list := node statements last statements.
  			 node statements removeLast; addAllLast: list]].
  	^labelUsed!



More information about the Vm-dev mailing list