[Vm-dev] VM Maker: CMakeVMMakerSqueak-tty.123.mcz

commits at source.squeak.org commits at source.squeak.org
Tue May 31 18:53:02 UTC 2016


Timothy M uploaded a new version of CMakeVMMakerSqueak to project VM Maker:
http://source.squeak.org/VMMaker/CMakeVMMakerSqueak-tty.123.mcz

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

Name: CMakeVMMakerSqueak-tty.123
Author: tty
Time: 31 May 2016, 1:58:37.446194 pm
UUID: dab66491-fde1-4c7f-8657-fd96bd87f3a6
Ancestors: CMakeVMMakerSqueak-tty.122

All tests green.

Refactored some tests.
Deleted some Builder tests that properly belong to Configurations.
Fixed a bug in CMakeVMakerConfigurationInfo where Abstract Base Class configurations where not accounted for.

=============== Diff against CMakeVMMakerSqueak-tty.122 ===============

Item was changed:
  ----- Method: CMakeVMMakerSqueakBuildersTest>>testAllAndNoneBuildTypes (in category 'as yet unclassified') -----
  testAllAndNoneBuildTypes
+ 	self assert: (SqueakCMakeVMMakerAbstractBuilder  allBuildTypes isKindOf: Collection).
  	self assert: (SqueakCMakeVMMakerAbstractBuilder  allBuildTypes size > 0).
  	self assert: (SqueakCMakeVMMakerAbstractBuilder  noBuildTypes isEmpty).
  	!

Item was removed:
- ----- Method: CMakeVMMakerSqueakBuildersTest>>testBuildDirectory (in category 'as yet unclassified') -----
- testBuildDirectory
- 	SqueakCMakeVMMakerAbstractBuilder 
- 		subclassesDo:[:builder | 
- 				self assert: (builder buildDirectory isString).
- 				self assert:(builder buildDirectory size > 0).
- 				]
- 
- !

Item was removed:
- ----- Method: CMakeVMMakerSqueakBuildersTest>>testSourceDirectoryFor (in category 'as yet unclassified') -----
- testSourceDirectoryFor
- 	SqueakCMakeVMMakerAbstractBuilder 
- 		subclassesDo:[:builder | 
- 				builder availableBuildConfigurations do:[:configuration | 
- 					self assert:((builder sourceDirectoryFor: configuration) isString).
- 					self assert:((builder sourceDirectoryFor: configuration) size > 0)]]
- 
- !

Item was added:
+ ----- Method: CMakeVMMakerSqueakBuildersTest>>testUnAvailableBuildConfigurations (in category 'as yet unclassified') -----
+ testUnAvailableBuildConfigurations
+ 	SqueakCMakeVMMakerAbstractBuilder 
+ 		subclassesDo:[:builder | 
+ 				self assert: (builder unAvailableBuildConfigurations isKindOf:Collection)]
+ 
+ !

Item was removed:
- ----- Method: CMakeVMMakerSqueakBuildersTest>>testUnavailableBuildConfigurations (in category 'as yet unclassified') -----
- testUnavailableBuildConfigurations
- 	SqueakCMakeVMMakerAbstractBuilder 
- 		subclassesDo:[:builder | 
- 				self assert: (builder unAvailableBuildConfigurations isKindOf:Collection)]
- 
- !

Item was changed:
  ----- Method: CMakeVMMakerSqueakCommonConfigTest>>testDirBuildPlatform (in category 'as yet unclassified') -----
  testDirBuildPlatform
  	"for each builder, make sure all its configurations provide a dirSource "
  	#(#SqueakMacintoshConfig #SqueakUnixConfig #SqueakWindowsConfig) 
  		do:[:each | 
  			(Smalltalk at:each) 
  				allSubclassesDo:[:configuration | | o |
  									o:= configuration basicNew.
  									self assert:(o  dirBuildPlatform isString)]]
  
  
  
  
  
  
  
  !

Item was added:
+ ----- Method: CMakeVMakerConfigurationInfo>>isAbstractBaseClass (in category 'accessing') -----
+ isAbstractBaseClass
+ 
+ 	^ isAbstractBaseClass!

Item was changed:
  ----- Method: CMakeVMakerConfigurationInfo>>visit: (in category 'visiting') -----
  visit: aVisitor
  	|v|
  	"I am being visited by a CMakeVMMakerSqueak configuration class. Extract its information and store it in myself"
  	self flag:'tty'. "why am I not storing the instances itself?does this visit stuff really make sense? I am thinking its 'lightweight'. hmmm"
  	v:= aVisitor basicNew.
  	(v class isAbstractBaseClass)
+ 		ifTrue:[	
+ 				isAbstractBaseClass := true.
+ 				excludeFromBuild := true]
  		ifFalse:[
  			availableBuildTypes := v availableBuildTypes.
  			dirBuildPlatform := v dirBuildPlatform.
- 			dirSource  := v dirSource.
  			excludeFromBuild := v excludeFromBuild.
+ 			isAbstractBaseClass := false]. 
- 			isAbstractBaseClass := (v class) isAbstractBaseClass].
  
  !

Item was changed:
  Object subclass: #SqueakCMakeVMMakerAbstractBuilder
  	instanceVariableNames: 'buildTypeAndDirectoryInfo config'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'CMakeVMMakerSqueak-Builder'!
  SqueakCMakeVMMakerAbstractBuilder class
  	instanceVariableNames: 'default'!
  
+ !SqueakCMakeVMMakerAbstractBuilder commentStamp: 'tty 5/31/2016 09:46' prior: 0!
- !SqueakCMakeVMMakerAbstractBuilder commentStamp: 'tty 2/7/2016 08:51' prior: 0!
  I am an abstract base class for various CMakeVMMakerSqueak builders.
  
  I am a singleton.
  I am a facade to the various Squeak[Platform][WordSize][VM][MemoryManager]Config classes
  I provide facilities to query my configurations.
  I use the Visitor pattern in collecting information about my configurations.
  
- HelpBrowser openOn: CMakeVMMakerSqueakDeveloperHelp.
  
  
+ (HelpBrowser openOn: CMakeVMMakerSqueakDeveloperHelp) model
+    showTopicThat: [:topic | topic title beginsWith: 'Builder']. 
  
  !
  SqueakCMakeVMMakerAbstractBuilder class
  	instanceVariableNames: 'default'!

Item was removed:
- ----- Method: SqueakCMakeVMMakerAbstractBuilder class>>dirBuildPlatform (in category 'queries') -----
- dirBuildPlatform
- 	default ifNil:[default:= self new].
- 	^default dirBuildPlatform!

Item was removed:
- ----- Method: SqueakCMakeVMMakerAbstractBuilder class>>sourceDirectoryFor: (in category 'queries') -----
- sourceDirectoryFor: aSymbol
- 	default ifNil:[default:= self new].
- 	^default sourceDirectoryFor: aSymbol!

Item was changed:
  ----- Method: SqueakCMakeVMMakerAbstractBuilder>>availableBuildConfigurationsFor: (in category 'queries') -----
  availableBuildConfigurationsFor: aCategoryName
+ 	"answer the CMakeVMakerSqueak configurations in a Smalltalk category that are neither Abstract Base Classes nor excluded from builds."
- 	"answer the CMakeVMakerSqueak configurations in a Smalltalk category that have not excluded themselves from being built."
  
- "	(((self configurationDictionary:aCategoryName) keys asSortedCollection) size = 0)      
- 		ifTrue:[^((self configurationDictionary:aCategoryName) keys asSortedCollection) sort]."
-      ^(((self configurationDictionary:aCategoryName) select: [:info| info value excludeFromBuild not ]) keys asSortedCollection) sort
  
+ 
+      ^((
+ 	    (self configurationDictionary:aCategoryName) select: [:info| (info isAbstractBaseClass not) &  (info excludeFromBuild not)]
+          ) keys asSortedCollection
+         ) sort.
+ 
  !

Item was changed:
  ----- Method: SqueakCMakeVMMakerAbstractBuilder>>availableBuildTypesFor:inCategory: (in category 'queries') -----
  availableBuildTypesFor: aSymbol inCategory: aCategoryName
  	|d |
  	"extract the CMakeVMakerConfigurationInfo object for a configuration and return the availableBuildTypes ."
  	d:=(self configurationDictionary:aCategoryName) at: aSymbol ifAbsent:[^SqueakCMakeVMMakerAbstractBuilder default noBuildConfigurations].
  	^d availableBuildTypes
  
  
  
  !

Item was removed:
- ----- Method: SqueakCMakeVMMakerAbstractBuilder>>dirBuildPlatform (in category 'queries') -----
- dirBuildPlatform
- 	"Answer the root directory for this configuration's build that contains build, build.assert...etc directories. example:  cmake_build.linux32x86."
- 	^self dirBuildPlatform:(self configurationsCategory)!

Item was removed:
- ----- Method: SqueakCMakeVMMakerAbstractBuilder>>dirBuildPlatform: (in category 'queries') -----
- dirBuildPlatform: aCategoryName
- 	|info|
- 	"All the configurations in a category share the same build platform."
- 	info:=(self configurationDictionary:aCategoryName) at: ((self configurationDictionary:aCategoryName) keys at:1).  "i.e. aDictionary at:1"
- 	^info dirBuildPlatform
- 	
- 	
- !

Item was removed:
- ----- Method: SqueakCMakeVMMakerAbstractBuilder>>getInfoForBuild: (in category 'queries') -----
- getInfoForBuild: aSymbol!

Item was changed:
  ----- Method: SqueakCMakeVMMakerAbstractBuilder>>getInfoForBuilds (in category 'queries') -----
  getInfoForBuilds
  	| result|
  	"return a Dictionary of CMakeMakerSqueak-XYZ platform configurations and their associated CMakeVMakerConfigurationInfo "
  	result := Dictionary new.
  	self class allSubclassesDo:[:c | |configurationsCategory |
  				configurationsCategory := c default configurationsCategory.
  				result at:(configurationsCategory asSymbol)  put: (self configurationDictionary: configurationsCategory).
  	].
  .	^result
  
  !

Item was changed:
  ----- Method: SqueakCMakeVMMakerAbstractBuilder>>initialize (in category 'initialization') -----
  initialize
  	"a stupid <cough>temporary</cough> hack to workaround initialization problems"
+ 	self flag:'tty. why is this here? its from pharo...'.
  	Cogit allSubclassesDo: [ :each | each initializeWithOptions: (VMMaker new instVarNamed: 'optionsDictionary') ].
+ "	scriptMode:= false. On the chance that we ever use scripts to invoke builders, here is  a flag to bypass user interaction/informs"
- 	scriptMode:= false. "On the chance that we ever use scripts to invoke builders, here is  a flag to bypass user interaction/informs"
  	self initializeBuildTypeAndDirectoryInfo.
  
  	!

Item was removed:
- ----- Method: SqueakCMakeVMMakerAbstractBuilder>>sourceDirectoryFor: (in category 'queries') -----
- sourceDirectoryFor: aSymbol
- 	"answer a subset of buildTypeAndDirectoryInfo based on the buildTypes the configuration supports   "
- 	[
- 	((Smalltalk at: aSymbol)  category) =  (self configurationsCategory)  "verify the class is handled by this concrete builder"
- 		ifTrue:[	^self sourceDirectoryFor: aSymbol inCategory: ((Smalltalk at: aSymbol)  category).]  "if so, go get its info"
- 		ifFalse:[^self userErrorInvalidTarget: aSymbol]
- 	] ifError:[^'sourceDirectoryFor: ''', aSymbol , ''' not found' ].
- 	^nil.!

Item was removed:
- ----- Method: SqueakCMakeVMMakerAbstractBuilder>>sourceDirectoryFor:inCategory: (in category 'queries') -----
- sourceDirectoryFor: aSymbol inCategory: aCategoryName
- 	|info |
- 	"extract the CMakeVMakerConfigurationInfo object for a configuration and return the sourceDirectory ."
- 	info:=(self configurationDictionary:aCategoryName) at: aSymbol ifAbsent:[^SqueakCMakeVMMakerAbstractBuilder default userErrorNoSource:aSymbol].
- 	^info dirSource
- 
- 
- 
- !

Item was changed:
  ----- Method: SqueakCMakeVMMakerAbstractBuilder>>unAvailableBuildConfigurationsFor: (in category 'queries') -----
  unAvailableBuildConfigurationsFor: aCategoryName
+ 	"answer the CMakeVMakerSqueak configurations in a Smalltalk category that are neither Abstract Base Classes nor excluded from builds."
- 	"answer the CMakeVMakerSqueak configurations in a Smalltalk category that havenot excluded themselves from being built."
  
- "	(((self configurationDictionary:aCategoryName) keys asSortedCollection) size = 0)      
- 		ifTrue:[^((self configurationDictionary:aCategoryName) keys asSortedCollection) sort]."
-      ^(((self configurationDictionary:aCategoryName) select: [:info| info value excludeFromBuild ]) keys asSortedCollection) sort
  
+ 
+      ^((
+ 	    (self configurationDictionary:aCategoryName) select: [:info| (info isAbstractBaseClass) |  (info excludeFromBuild)]
+          ) keys asSortedCollection
+         ) sort.
+ 
  !



More information about the Vm-dev mailing list