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

commits at source.squeak.org commits at source.squeak.org
Fri Feb 26 21:01:58 UTC 2016


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

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

Name: VMMaker.oscog-eem.1702
Author: eem
Time: 26 February 2016, 1:00:09.123061 pm
UUID: ca289ff1-8bc0-40d7-a4bb-42b583f02dd1
Ancestors: VMMaker.oscog-eem.1701

Eliminate some C compiler warnings in the generated code.
Add returns at the end of sqInt methods that don't end with a return.
Improve the variable pruning to mirror dead code elimination.

Make the leak checker operational in the non-assert (& non-debug) VM.

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

Item was changed:
  ----- Method: CCodeGenerator>>addMethodFor:selector: (in category 'utilities') -----
  addMethodFor: aClass selector: selector
  	"Add the given method to the code base and answer its translation
  	 or nil if it shouldn't be translated."
  
  	| method tmethod |
  	method := aClass compiledMethodAt: selector.
  	(method pragmaAt: #doNotGenerate) ifNotNil:
  		["only remove a previous method if this one overrides it, i.e. this is a subclass method.
  		 If the existing method is in a different hierarchy this method must be merely a redeirect."
  		 (methods at: selector ifAbsent: []) ifNotNil:
  			[:tm|
  			(aClass includesBehavior: tm definingClass) ifTrue:
  				[self removeMethodForSelector: selector]].
  		 ^nil].
  	method isSubclassResponsibility ifTrue:
  		[^nil].
  	(self shouldIncludeMethodFor: aClass selector: selector) ifFalse:
  		[^nil].
  	tmethod := self compileToTMethodSelector: selector in: aClass.
  	"Even thoug we exclude initialize methods, we must consider their
  	 global variable usage, otherwise globals may be incorrectly localized."
  	selector == #initialize ifTrue:
+ 		[self checkForGlobalUsage: (tmethod allReferencedVariablesUsing: self) in: tmethod.
- 		[self checkForGlobalUsage: (tmethod allReferencedVariablesIn: self) in: tmethod.
  		 ^nil].
  	self addMethod: tmethod.
  	"If the method has a macro then add the macro.  But keep the method
  	 for analysis purposes (e.g. its variable accesses)."
  	(method pragmaAt: #cmacro:) ifNotNil:
  		[:pragma|
  		self addMacro: (pragma argumentAt: 1) for: selector.
  		(inlineList includes: selector) ifTrue:
  			[inlineList := inlineList copyWithout: selector]].
  	(method pragmaAt: #cmacro) ifNotNil:
  		[:pragma| | literal | "Method should be just foo ^const"
  		self assert: (method numArgs = 0 and: [method numLiterals = 3 or: [method isQuick]]).
  		literal := method isQuick
  					ifTrue: [method decompile block statements last expr key]
  					ifFalse: [method literalAt: 1].
  		self addMacro: '() ', (self cLiteralFor: literal value name: method selector) for: selector.
  		(inlineList includes: selector) ifTrue:
  			[inlineList := inlineList copyWithout: selector]].
  	^tmethod!

Item was changed:
  ----- Method: CCodeGenerator>>nilOrBooleanConditionFor: (in category 'utilities') -----
  nilOrBooleanConditionFor: nodeOrNil
  	"If nodeOrNil is one of the conditional sends for which we do translation-time dead code elimination
  	 (i.e. cppIf:ifTrue: et al or ifTrue: et al) and the conditional does evaluate to a translation-time
  	 boolean constant, answer that constant, otherwise answer nil.  Used to prune dead code,
  	 either for code generaton or dead variable elimination."
  	generateDeadCode ifTrue: [^nil].
  	nodeOrNil ifNil:
  		[^nil].
  	nodeOrNil isSend ifFalse:
  		[^nil].
+ 	(#(ifTrue: ifFalse: ifTrue:ifFalse: ifFalse:ifTrue:) includes: nodeOrNil selector) ifTrue:
+ 		[^self nilOrBooleanConstantReceiverOf: nodeOrNil receiver].
+ 	(#(and: or:) includes: nodeOrNil selector) ifTrue:
+ 		[^self nilOrBooleanConstantReceiverOf: nodeOrNil].
  	(#(cppIf:ifTrue: cppIf:ifTrue:ifFalse:) includes: nodeOrNil selector) ifTrue:
  		[(vmClass notNil
  		 and: [nodeOrNil args first isConstant
  		 and: [nodeOrNil args first value isSymbol
  		 and: [(VMBasicConstants defineAtCompileTime: nodeOrNil args first value) not
  		 and: [(vmClass bindingOf: nodeOrNil args first value) notNil]]]]) ifTrue:
  			[self logger
  					nextPutAll: 'Warning: cppIf: reference to ';
  					store: nodeOrNil args first value;
  					nextPutAll: ' when variable of same name exists.'; cr].
  
  		 ^(optionsDictionary notNil
  		   and: [nodeOrNil args first isConstant
  		   and: [#(true false) includes: (optionsDictionary at: nodeOrNil args first name ifAbsent: [nil])]]) ifTrue:
  			[optionsDictionary at: nodeOrNil args first name]].
+ 	^nil!
- 
- 	^(#(ifTrue: ifFalse: ifTrue:ifFalse: ifFalse:ifTrue:) includes: nodeOrNil selector) ifTrue:
- 		[self nilOrBooleanConstantReceiverOf: nodeOrNil]!

Item was added:
+ ----- Method: CCodeGenerator>>nodeIsDeadCode:withParent: (in category 'utilities') -----
+ nodeIsDeadCode: aNode withParent: parentNode
+ 	"Answer if aNode would not be generated due to dead code elimination."
+ 	^(self nilOrBooleanConditionFor: parentNode)
+ 		ifNil: [false]
+ 		ifNotNil:
+ 			[:cond| | filter |
+ 			filter := parentNode selector caseOf:
+ 							{   "First element is accessor for filtered (eliminated) node if expression is true.
+ 								Second element is accessor for filtered (eliminated) node if expression is false."
+ 								[#ifFalse:]				-> [#(first nil)].
+ 								[#ifFalse:ifTrue:] 		-> [#(first last)].
+ 								[#ifTrue:]				-> [#(nil first)].
+ 								[#ifTrue:ifFalse:]			-> [#(last first)].
+ 								[#and:]					-> [#(nil first)].
+ 								[#or:]					-> [#(last nil)].
+ 								[#cppIf:ifTrue:]			-> [#(nil #second)].
+ 								[#cppIf:ifTrue:ifFalse:]	-> [#(third #second)] }.
+ 			(cond ifTrue: [filter first] ifFalse: [filter last])
+ 				ifNil: [false]
+ 				ifNotNil: [:accessor| aNode == (parentNode args perform: accessor)]]!

Item was changed:
  ----- Method: CoInterpreter>>commenceCogCompiledCodeCompaction (in category 'process primitive support') -----
  commenceCogCompiledCodeCompaction
  	| startTime |
  	<var: #startTime type: #usqLong>
  	cogCompiledCodeCompactionCalledFor := false.
  	cogit recordEventTrace ifTrue:
  		[self recordTrace: TraceCodeCompaction thing: TraceCodeCompaction source: 0].
  	cogit recordPrimTrace ifTrue:
  		[self fastLogPrim: TraceCodeCompaction].
  	startTime := self ioUTCMicrosecondsNow.
  
  	"This can be called in a number of circumstances.  The instructionPointer
  	 may contain a native pc that must be relocated.  There may already be a
  	 pushed instructionPointer on stack.  Clients ensure that instructionPointer
  	 is 0 if it should not be pushed and/or relocated.  Pushing twice is a mistake
  	 because only the top one will be relocated."
  	instructionPointer ~= 0 ifTrue:
  		["better not have already been pushed"
  		 self assert: self stackTop asUnsignedInteger ~= instructionPointer.
  		 self push: instructionPointer.
  		 self externalWriteBackHeadStackPointer].
  	self assertValidStackedInstructionPointers: #'__LINE__'.
  	cogit compactCogCompiledCode.
  	instructionPointer ~= 0 ifTrue:
  		[instructionPointer := self popStack.
  		 self externalWriteBackHeadStackPointer].
  	self assertValidStackedInstructionPointers: #'__LINE__'.
  
  	statCodeCompactionCount := statCodeCompactionCount + 1.
  	statCodeCompactionUsecs := statCodeCompactionUsecs + (self ioUTCMicrosecondsNow - startTime).
  
  	objectMemory checkForLeaks ~= 0 ifTrue:
  		[objectMemory clearLeakMapAndMapAccessibleObjects.
+ 		 self asserta: (self checkCodeIntegrity: false)]!
- 		 self assert: (self checkCodeIntegrity: false)]!

Item was changed:
  ----- Method: Cogit>>markAndTraceMachineCodeForNewSpaceGC (in category 'jit - api') -----
  markAndTraceMachineCodeForNewSpaceGC
  	"Free any methods that refer to unmarked objects, unlinking sends to freed methods."
  	| pointer cogMethod |
  	<var: #cogMethod type: #'CogMethod *'>
  	objectMemory leakCheckNewSpaceGC ifTrue:
+ 		[self asserta: self allMachineCodeObjectReferencesValid].
- 		[self assert: self allMachineCodeObjectReferencesValid].
  	codeModified := false.
  	pointer := methodZone youngReferrers.
  	[pointer < methodZone zoneEnd] whileTrue:
  		[cogMethod := coInterpreter cCoerceSimple: (objectMemory longAt: pointer) to: #'CogMethod *'.
  		 cogMethod cmRefersToYoung ifTrue:
  			[self assert: (self cogMethodDoesntLookKosher: cogMethod) = 0.
  			 self assert: (cogMethod cmType = CMMethod
  						or: [cogMethod cmType = CMOpenPIC]).
  			 (objectMemory isYoung: cogMethod selector) ifTrue:
  				[objectMemory markAndTrace: cogMethod selector].
  			 cogMethod cmType = CMMethod ifTrue:
  				[(objectMemory isYoung: cogMethod methodObject) ifTrue:
  					[objectMemory markAndTrace: cogMethod methodObject].
  				self markYoungObjectsIn: cogMethod]].
  		 pointer := pointer + objectMemory wordSize].
  	objectMemory leakCheckNewSpaceGC ifTrue:
+ 		[self asserta: self allMachineCodeObjectReferencesValid].
- 		[self assert: self allMachineCodeObjectReferencesValid].
  	codeModified ifTrue: "After updating oops in inline caches we need to flush the icache."
  		[processor flushICacheFrom: methodZoneBase asUnsignedInteger to: methodZone limitZony asUnsignedInteger]!

Item was changed:
  ----- Method: Cogit>>markAndTraceMachineCodeOfMarkedMethods (in category 'jit - api') -----
  markAndTraceMachineCodeOfMarkedMethods
  	"Mark objects in machine-code of marked methods (or open PICs with marked selectors)."
  	<api>
  	<option: #SpurObjectMemory>
  	| cogMethod |
  	<var: #cogMethod type: #'CogMethod *'>
  	objectMemory leakCheckFullGC ifTrue:
+ 		[self asserta: self allMachineCodeObjectReferencesValid].
- 		[self assert: self allMachineCodeObjectReferencesValid].
  	codeModified := false.
  	self markAndTraceObjectReferencesInGeneratedRuntime.
  	cogMethod := self cCoerceSimple: methodZoneBase to: #'CogMethod *'.
  	[cogMethod < methodZone limitZony] whileTrue:
  		[(cogMethod cmType = CMMethod
  		  and: [objectMemory isMarked: cogMethod methodObject]) ifTrue:
  			[self markAndTraceLiteralsIn: cogMethod].
  		 (cogMethod cmType = CMOpenPIC
  		  and: [(objectMemory isImmediate: cogMethod selector)
  				or: [objectMemory isMarked: cogMethod selector]]) ifTrue:
  			[self markAndTraceLiteralsIn: cogMethod].
  		 cogMethod := methodZone methodAfter: cogMethod].
  	objectMemory leakCheckFullGC ifTrue:
+ 		[self asserta: self allMachineCodeObjectReferencesValid].
- 		[self assert: self allMachineCodeObjectReferencesValid].
  	codeModified ifTrue: "After updating oops in inline caches we need to flush the icache."
  		[processor flushICacheFrom: methodZoneBase asUnsignedInteger to: methodZone limitZony asUnsignedInteger]!

Item was changed:
  ----- Method: Cogit>>markAndTraceOrFreeMachineCodeForFullGC (in category 'jit - api') -----
  markAndTraceOrFreeMachineCodeForFullGC
  	"Free any methods that refer to unmarked objects, unlinking sends to freed methods."
  	| cogMethod |
  	<var: #cogMethod type: #'CogMethod *'>
  	objectMemory leakCheckFullGC ifTrue:
+ 		[self asserta: self allMachineCodeObjectReferencesValid].
- 		[self assert: self allMachineCodeObjectReferencesValid].
  	codeModified := false.
  	self markAndTraceObjectReferencesInGeneratedRuntime.
  	cogMethod := self cCoerceSimple: methodZoneBase to: #'CogMethod *'.
  	[cogMethod < methodZone limitZony] whileTrue:
  		[self markAndTraceOrFreeCogMethod: cogMethod firstVisit: true.
  		 cogMethod := methodZone methodAfter: cogMethod].
  	objectMemory leakCheckFullGC ifTrue:
+ 		[self asserta: self allMachineCodeObjectReferencesValid].
- 		[self assert: self allMachineCodeObjectReferencesValid].
  	codeModified ifTrue: "After updating oops in inline caches we need to flush the icache."
  		[processor flushICacheFrom: methodZoneBase asUnsignedInteger to: methodZone limitZony asUnsignedInteger]!

Item was changed:
  ----- Method: SpurMemoryManager>>inLineRunLeakCheckerFor:excludeUnmarkedNewSpaceObjs:classIndicesShouldBeValid: (in category 'debug support') -----
  inLineRunLeakCheckerFor: gcModes excludeUnmarkedNewSpaceObjs: excludeUnmarkedNewSpaceObjs classIndicesShouldBeValid: classIndicesShouldBeValid
  	<inline: true>
  	(gcModes anyMask: checkForLeaks) ifTrue:
  		[(gcModes anyMask: GCModeFull)
  			ifTrue: [coInterpreter reverseDisplayFrom: 0 to: 7]
  			ifFalse: [coInterpreter reverseDisplayFrom: 8 to: 15].
  		 self clearLeakMapAndMapAccessibleObjects.
+ 		 self asserta: (self checkHeapIntegrity: excludeUnmarkedNewSpaceObjs classIndicesShouldBeValid: classIndicesShouldBeValid).
+ 		 self asserta: coInterpreter checkInterpreterIntegrity.
+ 		 self asserta: coInterpreter checkStackIntegrity.
+ 		 self asserta: (coInterpreter checkCodeIntegrity: gcModes)]!
- 		 self assert: (self checkHeapIntegrity: excludeUnmarkedNewSpaceObjs classIndicesShouldBeValid: classIndicesShouldBeValid).
- 		 self assert: coInterpreter checkInterpreterIntegrity.
- 		 self assert: coInterpreter checkStackIntegrity.
- 		 self assert: (coInterpreter checkCodeIntegrity: gcModes)]!

Item was changed:
  ----- Method: SpurMemoryManager>>runLeakCheckerForFreeSpace: (in category 'debug support') -----
  runLeakCheckerForFreeSpace: gcModes
  	<inline: false>
  	(gcModes anyMask: GCModeFreeSpace) ifTrue:
  		[coInterpreter reverseDisplayFrom: 16 to: 19.
  		 self clearLeakMapAndMapAccessibleFreeSpace.
+ 		 self asserta: self checkHeapFreeSpaceIntegrity]!
- 		 self assert: self checkHeapFreeSpaceIntegrity]!

Item was changed:
  ----- Method: StackInterpreter class>>declareCVarsIn: (in category 'translation') -----
  declareCVarsIn: aCCodeGenerator
  	| vmClass |
  	self class == thisContext methodClass ifFalse: [^self]. "Don't duplicate decls in subclasses"
  	vmClass := aCCodeGenerator vmClass. "Generate primitiveTable etc based on vmClass, not just StackInterpreter"
  	aCCodeGenerator
  		addHeaderFile:'<stddef.h> /* for e.g. alloca */';
  		addHeaderFile:'<setjmp.h>';
  		addHeaderFile:'<wchar.h> /* for wint_t */';
  		addHeaderFile:'"vmCallback.h"';
  		addHeaderFile:'"sqMemoryFence.h"';
  		addHeaderFile:'"dispdbg.h"'.
  	vmClass declareInterpreterVersionIn: aCCodeGenerator defaultName: 'Stack'.
  	aCCodeGenerator
  		var: #interpreterProxy  type: #'struct VirtualMachine*'.
  	aCCodeGenerator
  		declareVar: #sendTrace type: 'volatile int';
  		declareVar: #byteCount type: 'unsigned long'.
  	"These need to be pointers or unsigned."
  	self declareC: #(instructionPointer method newMethod)
  		as: #usqInt
  		in: aCCodeGenerator.
  	"These are all pointers; char * because Slang has no support for C pointer arithmetic."
+ 	self declareC: #(localIP localSP localFP stackPointer framePointer stackLimit breakSelector)
- 	self declareC: #(localIP localSP localFP stackPointer framePointer stackLimit stackMemory breakSelector)
  		as: #'char *'
  		in: aCCodeGenerator.
  	aCCodeGenerator
  		var: #breakSelectorLength
  		declareC: 'sqInt breakSelectorLength = MinSmallInteger'.
  	self declareC: #(stackPage overflowedPage)
  		as: #'StackPage *'
  		in: aCCodeGenerator.
  	aCCodeGenerator removeVariable: 'stackPages'.  "this is an implicit receiver in the translated code."
  	NewspeakVM ifFalse:
  		[aCCodeGenerator
  			removeVariable: 'localAbsentReceiver';
  			removeVariable: 'localAbsentReceiverOrZero';
  			removeVariable: 'nsMethodCache'].
  	"This defines bytecodeSetSelector as 0 if MULTIPLEBYTECODESETS
  	 is not defined, for the benefit of the interpreter on slow machines."
  	aCCodeGenerator addConstantForBinding: (self bindingOf: #MULTIPLEBYTECODESETS).
  	MULTIPLEBYTECODESETS == false ifTrue:
  		[aCCodeGenerator
  			removeVariable: 'extA';
  			removeVariable: 'extB';
  			removeVariable: 'bytecodeSetSelector'].
  	aCCodeGenerator
  		var: #methodCache
  		declareC: 'long methodCache[MethodCacheSize + 1 /* ', (MethodCacheSize + 1) printString, ' */]'.
  	aCCodeGenerator
  		var: #nsMethodCache
  		declareC: 'long nsMethodCache[NSMethodCacheSize + 1 /* ', (NSMethodCacheSize + 1) printString, ' */]'.
  	AtCacheTotalSize isInteger ifTrue:
  		[aCCodeGenerator
  			var: #atCache
  			declareC: 'sqInt atCache[AtCacheTotalSize + 1 /* ', (AtCacheTotalSize + 1) printString, ' */]'].
  	aCCodeGenerator
  		var: #primitiveTable
  		declareC: 'void (*primitiveTable[MaxPrimitiveIndex + 2 /* ', (MaxPrimitiveIndex + 2) printString, ' */])(void) = ', vmClass primitiveTableString.
  	vmClass primitiveTable do:
  		[:symbolOrNot|
  		(symbolOrNot isSymbol
  		 and: [symbolOrNot ~~ #primitiveFail]) ifTrue:
  			[(aCCodeGenerator methodNamed: symbolOrNot) ifNotNil:
  				[:tMethod| tMethod returnType: #void]]].
  	vmClass objectMemoryClass hasSpurMemoryManagerAPI
  		ifTrue:
  			[aCCodeGenerator
  				var: #primitiveAccessorDepthTable
  				type: 'signed char'
  				sizeString: 'MaxPrimitiveIndex + 2 /* ', (MaxPrimitiveIndex + 2) printString, ' */'
  				array: vmClass primitiveAccessorDepthTable]
  		ifFalse:
  			[aCCodeGenerator removeVariable: #primitiveAccessorDepthTable].
  	aCCodeGenerator
  		var: #primitiveFunctionPointer
  		declareC: 'void (*primitiveFunctionPointer)()'.
  	aCCodeGenerator
  		var: #externalPrimitiveTable
  		declareC: 'void (*externalPrimitiveTable[MaxExternalPrimitiveTableSize + 1 /* ', (MaxExternalPrimitiveTableSize + 1) printString, ' */])(void)'.
  	aCCodeGenerator var: #showSurfaceFn type: #'void *'.
  	aCCodeGenerator
  		var: #jmpBuf
  		declareC: 'jmp_buf jmpBuf[MaxJumpBuf + 1 /* ', (MaxJumpBuf + 1) printString, ' */]'.
  	aCCodeGenerator
  		var: #suspendedCallbacks
  		declareC: 'usqInt suspendedCallbacks[MaxJumpBuf + 1 /* ', (MaxJumpBuf + 1) printString, ' */]'.
  	aCCodeGenerator
  		var: #suspendedMethods
  		declareC: 'usqInt suspendedMethods[MaxJumpBuf + 1 /* ', (MaxJumpBuf + 1) printString, ' */]'.
  	aCCodeGenerator
  		var: #interruptCheckChain
  		declareC: 'void (*interruptCheckChain)(void) = 0'.
  
  	self declareCAsUSqLong: #(nextPollUsecs nextWakeupUsecs longRunningPrimitiveGCUsecs
  								longRunningPrimitiveStartUsecs longRunningPrimitiveStopUsecs
  								"these are high-frequency enough that they're overflowing quite quickly on modern hardware"
  								statProcessSwitch statIOProcessEvents statForceInterruptCheck
  								statCheckForEvents statStackOverflow statStackPageDivorce)
  		in: aCCodeGenerator.
  	aCCodeGenerator var: #nextProfileTick type: #sqLong!

Item was removed:
- ----- Method: TMethod>>allReferencedVariablesIn: (in category 'accessing') -----
- allReferencedVariablesIn: aCodeGen
- 	"Answer the set of all variables referenced in the receiver."
- 	| refs |
- 	refs := Set new.
- 	"Find all the variable names referenced in this method.
- 	 Don't descend into "
- 	parseTree
- 		nodesWithParentsDo:
- 			[:node :parent|
- 			node isVariable ifTrue: [refs add: node name asString].
- 			node isStmtList ifTrue: [refs addAll: node args].
- 			(node isSend
- 			 and: [node selector beginsWith: #cCode:]) ifTrue:
- 				[aCodeGen addVariablesInVerbatimCIn: node to: refs]]
- 		unless:
- 			[:node :parent|
- 			(aCodeGen nilOrBooleanConditionFor: parent)
- 				ifNil: [false]
- 				ifNotNil:
- 					[:condition| "double negatives are confusing, aren't they ;-)"
- 					node = parent args second == condition not]].
- 	^refs!

Item was added:
+ ----- Method: TMethod>>allReferencedVariablesUsing: (in category 'accessing') -----
+ allReferencedVariablesUsing: aCodeGen
+ 	"Answer the set of all variables referenced in the receiver."
+ 	| refs |
+ 	refs := Set new.
+ 	"Find all the variable names referenced in this method.
+ 	 Don't descend into conditionals that won't be generated."
+ 	parseTree
+ 		nodesWithParentsDo:
+ 			[:node :parent|
+ 			node isVariable ifTrue: [refs add: node name asString].
+ 			node isStmtList ifTrue: [refs addAll: node args].
+ 			(node isSend
+ 			 and: [node selector beginsWith: #cCode:]) ifTrue:
+ 				[aCodeGen addVariablesInVerbatimCIn: node to: refs]]
+ 		unless:
+ 			[:node :parent|
+ 			parent notNil
+ 			and: [parent isSend
+ 			and: [aCodeGen nodeIsDeadCode: node withParent: parent]]].
+ 	^refs!

Item was changed:
  ----- Method: TMethod>>removeUnusedTempsIn: (in category 'utilities') -----
  removeUnusedTempsIn: aCodeGen
  	"Remove all of the unused temps in this method. Answer a set of the references."
  	"After inlining some variable references are now obsolete, we could fix them there
  	 but the code seems a bit complicated, the other choice to to rebuild the locals
  	 before extruding. This is done here"
+ 	| usedVariables |
+ 	usedVariables := self allReferencedVariablesUsing: aCodeGen.
- 	| refs |
- 	refs := self allReferencedVariablesIn: aCodeGen.
  	"reset the locals to be only those still referred to"
+ 	locals do:
+ 		[:local|
+ 		 ((usedVariables includes: local) not
+ 		  and: [((declarations at: local ifAbsent: ['']) includesSubString: 'static') not
+ 		  and: [((declarations at: local ifAbsent: ['']) includesSubString: 'extern') not]]) ifTrue:
+ 			[locals remove: local.
+ 			 declarations removeKey: local ifAbsent: []]].
+ 	^usedVariables!
- 	locals := locals select: [:e| refs includes: e].
- 	^refs!



More information about the Vm-dev mailing list