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

commits at source.squeak.org commits at source.squeak.org
Tue Dec 27 05:11:48 UTC 2016


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

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

Name: VMMaker.oscog-eem.2051
Author: eem
Time: 26 December 2016, 9:11:06.091387 pm
UUID: facc9a57-b736-4608-9126-484f4da4905b
Ancestors: VMMaker.oscog-eem.2050

Nuke the exportAPISelectors: nonsense since we can use isAPIMetod on the methods set (I guess since apiMethods were available separately?).

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

Item was changed:
  ----- Method: CCodeGenerator>>emitCAPIExportHeaderOn: (in category 'C code generator') -----
  emitCAPIExportHeaderOn: aStream 
  	"Store prototype declarations for all non-inlined methods on the given stream."
+ 	| apiMethods usedConstants |
+ 	apiMethods := self sortMethods: (methods select: [:m| m isAPIMethod]).
+ 	apiMethods do:
- 	| api methodList usedConstants |
- 	api := (vmClass translationClass exportAPISelectors: self options).
- 	methodList := api
- 					select:
- 						[:s|
- 						(methods includesKey: s)
- 						or: [(vmClass whichClassIncludesSelector: s)
- 								ifNil: [false]
- 								ifNotNil: [:c|self shouldIncludeMethodFor: c selector: s]]]
- 					thenCollect:
- 						[:s|
- 						methods
- 							at: s
- 							ifAbsent: [self compileToTMethodSelector: s
- 										   in: (vmClass whichClassIncludesSelector: s)]].
- 	methodList := self sortMethods: methodList.
- 	methodList do:
  		[:m|
  		m static ifTrue:
  			[logger ensureCr; show: m selector, ' excluded from export API because it is static'; cr]].
+ 	self emitCFunctionPrototypes: apiMethods on: aStream.
- 	self emitCFunctionPrototypes: methodList on: aStream.
  	self emitGlobalCVariablesOn: aStream.
+ 	usedConstants := self emitCMacros: apiMethods on: aStream.
- 	usedConstants := self emitCMacros: methodList on: aStream.
  	self emitCConstants: usedConstants on: aStream!

Item was removed:
- ----- Method: CoInterpreter class>>exportAPISelectors: (in category 'translation') -----
- exportAPISelectors: options
- 	"Yes this is a mess.  When all exportAPI methods are marked with the <api> pragma
- 	 this can go away."
- 	| omExports |
- 	omExports := (self objectMemoryClass withAllSuperclasses copyUpTo: VMClass)
- 					inject: Set new into: [:api :c| api addAll: (c exportAPISelectors: options); yourself].
- 	^(self withAllSuperclasses copyUpTo: VMClass), (self ancilliaryClasses: options)
- 		inject: omExports
- 		into: [:set :class| set addAll: (self exportAPISelectorsFor: class); yourself]!

Item was removed:
- ----- Method: Cogit class>>exportAPISelectors: (in category 'translation') -----
- exportAPISelectors: options
- 	^((self withAllSuperclasses copyUpThrough: Cogit), (self ancilliaryClasses: options) collect:
- 		[:c| self exportAPISelectorsFor: c]) fold: [:a :b| a, b]!

Item was changed:
  ----- Method: Cogit class>>preGenerationHook: (in category 'translation') -----
  preGenerationHook: aCCodeGenerator
  	"Perform any last-minute changes to the code generator immediately
  	 before it performs code analysis and generation.  In this case, make
  	 all non-exported methods private."
- 	| exportAPISelectors |
- 	exportAPISelectors := self exportAPISelectors: aCCodeGenerator options.
  	aCCodeGenerator selectorsAndMethodsDo:
  		[:s :m|
+ 		m isAPIMethod
- 		(exportAPISelectors includes: s)
  			ifTrue: [m static: false]
  			ifFalse:
  				[m export ifFalse:
  					[m static: true]]]!

Item was changed:
  ----- Method: Cogit class>>requiredMethodNames: (in category 'translation') -----
  requiredMethodNames: options
  	"self requiredMethodNames"
+ 	^self tableFunctions!
- 	^(self exportAPISelectors: options)
- 		addAll: self tableFunctions;
- 		yourself!

Item was removed:
- ----- Method: ObjectMemory class>>requiredMethodNames: (in category 'translation') -----
- requiredMethodNames: options
- 	"return the list of method names that should be retained for export or other support reasons"
- 	^self exportAPISelectors: options!

Item was removed:
- ----- Method: Spur32BitCoMemoryManager class>>exportAPISelectors: (in category 'translation') -----
- exportAPISelectors: options
- 	^(Set withAll: (self exportAPISelectorsFor: self))
- 		addAll: (SpurGenerationScavenger exportAPISelectors: options);
- 		addAll: (self compactorClass exportAPISelectors: options);
- 		yourself!

Item was removed:
- ----- Method: Spur64BitCoMemoryManager class>>exportAPISelectors: (in category 'translation') -----
- exportAPISelectors: options
- 	^(Set withAll: (self exportAPISelectorsFor: self))
- 		addAll: (SpurGenerationScavenger exportAPISelectors: options);
- 		addAll: (self compactorClass exportAPISelectors: options);
- 		yourself!

Item was removed:
- ----- Method: SpurMemoryManager class>>requiredMethodNames: (in category 'translation') -----
- requiredMethodNames: options
- 	"return the list of method names that should be retained for export or other support reasons"
- 	^(self exportAPISelectors: options),
- 	  (SpurGenerationScavenger exportAPISelectors: options)!

Item was removed:
- ----- Method: StackInterpreter class>>exportAPISelectors: (in category 'translation') -----
- exportAPISelectors: options
- 	| omExports |
- 	omExports := (self objectMemoryClass withAllSuperclasses copyUpTo: VMClass)
- 					inject: Set new
- 					into: [:api :c| api addAll: (c exportAPISelectors: options); yourself].
- 	^(self withAllSuperclasses copyUpTo: VMClass), (self ancilliaryClasses: options)
- 		inject: omExports
- 		into: [:set :class| set addAll: (self exportAPISelectorsFor: class); yourself]!

Item was changed:
  ----- Method: StackInterpreter class>>preGenerationHook: (in category 'translation') -----
  preGenerationHook: aCCodeGen
  	"Perform any last-minute changes to the code generator immediately
  	 before it performs code analysis and generation.  In this case, make
  	 all non-exported methods private."
  	| publicMethodNames |
  	self primitiveTable do:
  		[:s|
  		(s isSymbol and: [s ~~ #primitiveFail]) ifTrue:
  			[(aCCodeGen methodNamed: s) returnType: #void]].
  	publicMethodNames := (self requiredMethodNames: aCCodeGen options)
  								copyWithoutAll: (self primitiveTable
  														copyWithout: #primitiveFail).
  	aCCodeGen selectorsAndMethodsDo:
  		[:s :m|
+ 		(m export or: [m isAPIMethod or: [publicMethodNames includes: s]]) ifTrue:
- 		(m export or: [publicMethodNames includes: s]) ifTrue:
  			[m static: false]]!

Item was changed:
  ----- Method: StackInterpreter class>>requiredMethodNames: (in category 'translation') -----
  requiredMethodNames: options
+ 	"Answer the list of method names that should be retained for export or other support reasons"
- 	"return the list of method names that should be retained for export or other support reasons"
  	| requiredList |
+ 	"A number of methods required by VM support code, specific platforms, etc"
+ 	requiredList := #(
- 	requiredList := self exportAPISelectors: options.
- 	requiredList addAll: (self objectMemoryClass requiredMethodNames: options).
- 	"A number of methods required by VM support code, jitter, specific platforms etc"
- 	requiredList addAll: #(
  		assertValidExecutionPointe:r:s:
  		characterForAscii:
  		findClassOfMethod:forReceiver: findSelectorOfMethod:
  			forceInterruptCheck forceInterruptCheckFromHeartbeat fullDisplayUpdate
  		getCurrentBytecode getFullScreenFlag getInterruptKeycode getInterruptPending
  			getSavedWindowSize getThisSessionID
  		interpret
  		loadInitialContext
  		primitiveFail primitiveFailFor: primitiveFlushExternalPrimitives printAllStacks printCallStack printContext:
  			printExternalHeadFrame printFramesInPage: printFrame: printHeadFrame printMemory printOop:
  				printStackPages printStackPageList printStackPagesInUse printStackPageListInUse
  		readableFormat: readImageFromFile:HeapSize:StartingAt:
  		setFullScreenFlag: setInterruptKeycode: setInterruptPending: setInterruptCheckChain:
  			setSavedWindowSize: success:
+ 		validInstructionPointer:inMethod:framePointer:) asSet.
- 		validInstructionPointer:inMethod:framePointer:).
  
  	"Nice to actually have all the primitives available"
  	requiredList addAll: (self primitiveTable select: [:each| each isSymbol]).
  
  	"InterpreterProxy is the internal analogue of sqVirtualMachine.c, so make sure to keep all those"
  	InterpreterProxy organization categories do:
  		[:cat |
  		((cat ~= 'initialize') and: [cat ~= 'private']) ifTrue:
  			[requiredList addAll: (InterpreterProxy organization listAtCategoryNamed: cat)]].
  
  	^requiredList!

Item was removed:
- ----- Method: VMClass class>>exportAPISelectors: (in category 'translation') -----
- exportAPISelectors: options
- 	^self exportAPISelectorsFor: self!

Item was removed:
- ----- Method: VMClass class>>exportAPISelectorsFor: (in category 'translation') -----
- exportAPISelectorsFor: aClass
- 	^(aClass selectors select:
- 		[:s| | m |
- 		((m := aClass compiledMethodAt: s) pragmaAt: #api) notNil or: [(m pragmaAt: #api:) notNil]]) asSet!



More information about the Vm-dev mailing list