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

commits at source.squeak.org commits at source.squeak.org
Sat Jun 7 21:03:10 UTC 2014


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

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

Name: CMakeVMMakerSqueak-tty.35
Author: tty
Time: 7 June 2014, 5:03:05.18 pm
UUID: 9ffafed4-4cbf-47b0-859b-468cb174ff6e
Ancestors: CMakeVMMakerSqueak-tty.34

CMakeVMMkaerSqeuakConfigurationsTest>>testBuildDirs passes.

This does not imply it is correct, but its a good sanity check that required methods are implemented.

=============== Diff against CMakeVMMakerSqueak-tty.34 ===============

Item was added:
+ ----- Method: CMakeVMMakerSqueakConfigurationsTest>>testBuildDirName (in category 'as yet unclassified') -----
+ testBuildDirName
+ 	"for each builder, make sure all its configurations provide a buildDirectory "
+ 	SqueakCMakeVMMakerAbstractBuilder 
+ 		subclassesDo:[:builder | | o |
+ 			Smalltalk globals 
+ 				allClassesDo:[:configuration | (configuration class category asString withoutQuoting startsWith: (builder configurationsCategory))
+ 					ifTrue:[ 
+ 							o:= configuration new.
+ 							self assert:(o  buildDirName isString)] 
+ 
+ ]]
+ 
+ 
+ 
+ 
+ 
+ 
+ 
+ !

Item was added:
+ ----- Method: CMakeVMMakerSqueakConfigurationsTest>>testDefaultExternalPlugins (in category 'as yet unclassified') -----
+ testDefaultExternalPlugins
+ 	"for each builder, make sure all its configurations provide a buildDirectory "
+ 	SqueakCMakeVMMakerAbstractBuilder 
+ 		subclassesDo:[:builder | | o |
+ 			Smalltalk globals 
+ 				allClassesDo:[:configuration | (configuration class category asString withoutQuoting startsWith: (builder configurationsCategory))
+ 					ifTrue:[ 
+ 							o:= configuration new.
+ 							self assert:(o  defaultExternalPlugins isArray)] 
+ 
+ ]]
+ 
+ 
+ 
+ 
+ 
+ 
+ 
+ !

Item was added:
+ ----- Method: CMakeVMMakerSqueakConfigurationsTest>>testDefaultInternalPlugins (in category 'as yet unclassified') -----
+ testDefaultInternalPlugins
+ 	"for each builder, make sure all its configurations provide a buildDirectory "
+ 	SqueakCMakeVMMakerAbstractBuilder 
+ 		subclassesDo:[:builder | | o |
+ 			Smalltalk globals 
+ 				allClassesDo:[:configuration | (configuration class category asString withoutQuoting startsWith: (builder configurationsCategory))
+ 					ifTrue:[ 
+ 							o:= configuration new.
+ 							self assert:(o  defaultInternalPlugins isArray)] 
+ 
+ ]]
+ 
+ 
+ 
+ 
+ 
+ 
+ 
+ !

Item was added:
+ ----- Method: CMakeVMMakerSqueakConfigurationsTest>>testExectuableName (in category 'as yet unclassified') -----
+ testExectuableName
+ 	"for each builder, make sure all its configurations provide a buildDirectory "
+ 	SqueakCMakeVMMakerAbstractBuilder 
+ 		subclassesDo:[:builder | | o |
+ 			Smalltalk globals 
+ 				allClassesDo:[:configuration | (configuration class category asString withoutQuoting startsWith: (builder configurationsCategory))
+ 					ifTrue:[ 
+ 							o:= configuration new.
+ 							self assert:(o  executableName isString)] 
+ 
+ ]]
+ 
+ 
+ 
+ 
+ 
+ 
+ 
+ !

Item was added:
+ ----- Method: CMakeVMMakerSqueakConfigurationsTest>>testExternalPlugins (in category 'as yet unclassified') -----
+ testExternalPlugins
+ 	"for each builder, make sure all its configurations provide a buildDirectory "
+ 	SqueakCMakeVMMakerAbstractBuilder 
+ 		subclassesDo:[:builder | | o |
+ 			Smalltalk globals 
+ 				allClassesDo:[:configuration | (configuration class category asString withoutQuoting startsWith: (builder configurationsCategory))
+ 					ifTrue:[ 
+ 							o:= configuration new.
+ 							self assert:(o  externalPlugins isArray)] 
+ 
+ ]]
+ 
+ 
+ 
+ 
+ 
+ 
+ 
+ !

Item was added:
+ ----- Method: CMakeVMMakerSqueakConfigurationsTest>>testInternalPlugins (in category 'as yet unclassified') -----
+ testInternalPlugins
+ 	"for each builder, make sure all its configurations provide a buildDirectory "
+ 	SqueakCMakeVMMakerAbstractBuilder 
+ 		subclassesDo:[:builder | | o |
+ 			Smalltalk globals 
+ 				allClassesDo:[:configuration | (configuration class category asString withoutQuoting startsWith: (builder configurationsCategory))
+ 					ifTrue:[ 
+ 							o:= configuration new.
+ 							self assert:(o  internalPlugins isArray)] 
+ 
+ ]]
+ 
+ 
+ 
+ 
+ 
+ 
+ 
+ !

Item was added:
+ ----- Method: CMakeVMMakerSqueakConfigurationsTest>>testOutputDir (in category 'as yet unclassified') -----
+ testOutputDir
+ 	"for each builder, make sure all its configurations provide a buildDirectory "
+ 	SqueakCMakeVMMakerAbstractBuilder 
+ 		subclassesDo:[:builder | | o |
+ 			Smalltalk globals 
+ 				allClassesDo:[:configuration | (configuration class category asString withoutQuoting startsWith: (builder configurationsCategory))
+ 					ifTrue:[ 
+ 							o:= configuration new.
+ 							self assert:(o  outputDir isKindOf: FileDirectory)] 
+ 
+ ]]
+ 
+ 
+ 
+ 
+ 
+ 
+ 
+ !

Item was changed:
  CPlatformConfig subclass: #Linux32x86Config
  	uses: TCPlatformConfigForSqueak
+ 	instanceVariableNames: 'buildType'
- 	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'CMakeVMMakerSqueak-Linux32x86'!
  
  !Linux32x86Config commentStamp: 'tty 6/7/2014 10:40' prior: 0!
  A Linux32x86Config is a Squeak Compatibility Layer between the Pharo code in CMakeVMMaker and CMakeVMakerSqueak.
  
  I exist because modifying the pharo tree is verbotten as of 2014.06.10
  
  !
  Linux32x86Config class
  	uses: TCPlatformConfigForSqueak classTrait
  	instanceVariableNames: ''!

Item was added:
+ ----- Method: Linux32x86Config>>buildDir (in category 'squeak compatibility') -----
+ buildDir
+ 	^ buildDir ifNil: [ buildDir := ( self topDir / self buildDirName) assureExistence].!

Item was added:
+ ----- Method: Linux32x86Config>>buildDirName (in category 'squeak compatibility') -----
+ buildDirName
+ 	buildType isNil
+ 		ifTrue:[^self dirBuildPlatform, self dirBuildLanguageVMMM, 'build']
+ 		ifFalse:[^self dirBuildPlatform, self dirBuildLanguageVMMM, buildType asString]!

Item was added:
+ ----- Method: Linux32x86Config>>buildType: (in category 'squeak compatibility') -----
+ buildType: aSymbol
+ 	buildType:= aSymbol!

Item was added:
+ ----- Method: Linux32x86Config>>dirBuildLanguageVMMM (in category 'cmake') -----
+ dirBuildLanguageVMMM
+ 	"the directory under buildPlatformDir  example: newspeak.cog.spur. use squeak.cog.v3 as default"
+ 	^self squeakCogV3!

Item was added:
+ ----- Method: Linux32x86Config>>dirBuildPlatform (in category 'cmake') -----
+ dirBuildPlatform
+ 	"the directory for the platform. example: build.linux32x86"
+ 	^self dirLinux32x86!

Item was added:
+ ----- Method: Linux32x86Config>>oscogvm (in category 'cmake') -----
+ oscogvm
+ 	^ 'oscogvm'!

Item was added:
+ ----- Method: Linux32x86Config>>topDir (in category 'squeak compatibility') -----
+ topDir
+ 	"N.B. this is a clash between Trait usage and Inheritence usage due to restrictions on modifying pharo's source"
+ 	^ topDir ifNil: [ topDir := FileDirectory default directoryNamed: self oscogvm ]
+ 	!

Item was added:
+ ----- Method: Linux32x86NewspeakStackV3Config>>dirBuildLanguageVMMM (in category 'as yet unclassified') -----
+ dirBuildLanguageVMMM
+ 	"the directory under buildPlatformDir  example: newspeak.cog.spur. use squeak.cog.v3 as default"
+ 	^self squeakStackV3!

Item was added:
+ ----- Method: Linux32x86SqueakCogSpurConfig>>dirBuildLanguageVMMM (in category 'as yet unclassified') -----
+ dirBuildLanguageVMMM
+ 	"the directory under buildPlatformDir  example: newspeak.cog.spur. use squeak.cog.v3 as default"
+ 	^self squeakCogSpur!

Item was changed:
  CogFamilyUnixConfig subclass: #Linux32x86SqueakCogV3Config
  	uses: TCPlatformConfigForSqueak
+ 	instanceVariableNames: 'buildType'
- 	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'CMakeVMMakerSqueak-Linux32x86'!
  
  !Linux32x86SqueakCogV3Config commentStamp: 'tty 6/7/2014 10:35' prior: 0!
  Base and concrete configuration for building a CogVM on Unix platform(s).
  
  Usage: 
  Linux32x86SqueakCogV3Config generateWithSources
  or
  Linux32x86SqueakCogV3Config generate   "if VMMaker sources already there"
  
  Or:
  find my Builder in CMakeVMMakerSqueak-Builder category and use that to query me or invoke me
  !
  Linux32x86SqueakCogV3Config class
  	uses: TCPlatformConfigForSqueak classTrait
  	instanceVariableNames: ''!

Item was changed:
  ----- Method: Linux32x86SqueakCogV3Config>>buildDirName (in category 'squeak compatibility') -----
  buildDirName
+ 	^ 'cmake_build.linux32x86'!
- 	^ 'cmake_unixbuild/bld'!

Item was added:
+ ----- Method: Linux32x86SqueakCogV3Config>>buildType: (in category 'squeak compatibility') -----
+ buildType: aSymbol
+ 	buildType:= aSymbol!

Item was added:
+ ----- Method: Linux32x86SqueakCogV3Config>>dirBuildLanguageVMMM (in category 'cmake') -----
+ dirBuildLanguageVMMM
+ 	"the directory under buildPlatformDir  example: newspeak.cog.spur. use squeak.cog.v3 as default"
+ 	^self squeakCogV3!

Item was changed:
  ----- Method: Linux32x86SqueakCogV3Config>>topDir (in category 'squeak compatibility') -----
  topDir
+ 	^ topDir ifNil: [ topDir := FileDirectory default directoryNamed: self oscogvm ]!
- 	^ topDir ifNil: [ topDir := FileDirectory default directoryNamed: 'oscogvm' ]!

Item was changed:
  CPlatformConfig subclass: #Linux32x86SqueakStackSpurConfig
  	uses: TCPlatformConfigForSqueak
+ 	instanceVariableNames: 'buildType'
- 	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'CMakeVMMakerSqueak-Linux32x86'!
  
  !Linux32x86SqueakStackSpurConfig commentStamp: 'tty 6/7/2014 10:34' prior: 0!
  A Linux32x86SqueakStackSpurConfig configures a VM according to my name's form: [Operating System] [WordSize] [Processor Language][VM MemoryManager][BuildType]Conf
  
  Usage:
  Linux32x86SqueakStackSpurConfig generate
  Or: 
  Linux32x86SqueakStackSpurConfig generateWithSources
  Or:
  find my Builder in CMakeVMMakerSqueak-Builder category and use that to query me or invoke me
  
  !
  Linux32x86SqueakStackSpurConfig class
  	uses: TCPlatformConfigForSqueak classTrait
  	instanceVariableNames: ''!

Item was added:
+ ----- Method: Linux32x86SqueakStackSpurConfig>>buildDir (in category 'squeak compatibility') -----
+ buildDir
+ 	^ buildDir ifNil: [ buildDir := ( self topDir / self buildDirName) assureExistence].!

Item was added:
+ ----- Method: Linux32x86SqueakStackSpurConfig>>buildDirName (in category 'squeak compatibility') -----
+ buildDirName
+ 	buildType isNil
+ 		ifTrue:[^self dirBuildPlatform, self dirBuildLanguageVMMM, 'build']
+ 		ifFalse:[^self dirBuildPlatform, self dirBuildLanguageVMMM, buildType asString]!

Item was added:
+ ----- Method: Linux32x86SqueakStackSpurConfig>>buildType: (in category 'squeak compatibility') -----
+ buildType: aSymbol
+ 	buildType:= aSymbol!

Item was added:
+ ----- Method: Linux32x86SqueakStackSpurConfig>>dirBuildLanguageVMMM (in category 'cmake') -----
+ dirBuildLanguageVMMM
+ 	"the directory under buildPlatformDir  example: newspeak.cog.spur"
+ 	^self squeakStackSpur!

Item was added:
+ ----- Method: Linux32x86SqueakStackSpurConfig>>dirBuildPlatform (in category 'cmake') -----
+ dirBuildPlatform
+ 	"the directory for the platform. example: build.linux32x86"
+ 	^self dirLinux32x86!

Item was added:
+ ----- Method: Linux32x86SqueakStackSpurConfig>>topDir (in category 'squeak compatibility') -----
+ topDir
+ 		^ topDir ifNil: [ topDir := FileDirectory default directoryNamed: self oscogvm ]!

Item was changed:
  StackUnixConfig subclass: #Linux32x86SqueakStackV3Config
  	uses: TCPlatformConfigForSqueak
+ 	instanceVariableNames: 'buildType'
- 	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'CMakeVMMakerSqueak-Linux32x86'!
  
  !Linux32x86SqueakStackV3Config commentStamp: 'tty 6/7/2014 10:33' prior: 0!
  A Linux32x86SqueakStackV3Config  configures a VM according to my name's form: [Operating System] [WordSize] [Processor Language][VM MemoryManager][BuildType]Conf
  
  Usage: 
  Linux32x86SqueakStackV3Config generate
  Or: 
  Linux32x86SqueakStackV3Config generateWithSources
  Or: 
  find my Builder in CMakeVMMakerSqueak-Builder category and use that to query me or invoke me
  !
  Linux32x86SqueakStackV3Config class
  	uses: TCPlatformConfigForSqueak classTrait
  	instanceVariableNames: ''!

Item was added:
+ ----- Method: Linux32x86SqueakStackV3Config>>buildLanguageVMMMDir (in category 'squeak compatibility') -----
+ buildLanguageVMMMDir
+ 	"the directory under buildPlatformDir  example: newspeak.cog.spur"
+ 	^self squeakStackV3!

Item was added:
+ ----- Method: Linux32x86SqueakStackV3Config>>buildPlatformDir (in category 'squeak compatibility') -----
+ buildPlatformDir
+ 	"the directory for the platform. example: build.linux32x86"
+ 	^self dirLinux32x86!

Item was added:
+ ----- Method: Linux32x86SqueakStackV3Config>>buildType: (in category 'squeak compatibility') -----
+ buildType: aSymbol
+ 	buildType:= aSymbol!

Item was added:
+ ----- Method: Linux32x86SqueakStackV3Config>>dirBuildLanguageVMMM (in category 'cmake') -----
+ dirBuildLanguageVMMM
+ 	"the directory under buildPlatformDir  example: newspeak.cog.spur. use squeak.cog.v3 as default"
+ 	^self squeakStackV3!

Item was changed:
  ----- Method: Linux32x86SqueakStackV3Config>>topDir (in category 'squeak compatibility') -----
  topDir
+ 	^ topDir ifNil: [ topDir := FileDirectory default directoryNamed: self oscogvm ]!
- 	^ topDir ifNil: [ topDir := FileDirectory default directoryNamed: 'oscogvm' ]!

Item was changed:
  Linux32x86SqueakCogV3Config subclass: #Linux64SqueakCogSpur
- 	uses: TCPlatformConfigForSqueak
  	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'CMakeVMMakerSqueak-LinuxX86_64'!
- 
- !Linux64SqueakCogSpur commentStamp: 'tty 6/7/2014 10:30' prior: 0!
- Linux64SqueakCogSpur has not been coded yet.
- 
- I am a placeholder for the upcoming Spur release in 2014.
- 
- Usage:
- Linux64SqueakCogSpur generate
- Or:
- Linux64SqueakCogSpur generateWithSources
- Or:
- find my Builder in CMakeVMMakerSqueak-Builder category and use that to query me or invoke me
- 
- 
- !
- Linux64SqueakCogSpur class
- 	uses: TCPlatformConfigForSqueak classTrait
- 	instanceVariableNames: ''!

Item was removed:
- ----- Method: Linux64SqueakCogSpur>>todo (in category 'as yet unclassified') -----
- todo
- 	self flag:'tty'!

Item was changed:
  CPlatformConfig subclass: #SqueakAndroidStackEvtConfig
  	uses: TCPlatformConfigForSqueak
+ 	instanceVariableNames: 'buildType'
- 	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'CMakeVMMakerSqueak-Android'!
  
  !SqueakAndroidStackEvtConfig commentStamp: 'tty 5/21/2014 12:18' prior: 0!
  A class to configure the Event-driven Stack Cog for Android. This configuration does not lead to building an executable; rather it prepares the source tree to be plugged into the jni subdirectory of an Android project.
  
  Requires AndroidPlugin
  
  Ported from pharo to squeak. !
  SqueakAndroidStackEvtConfig class
  	uses: TCPlatformConfigForSqueak classTrait
  	instanceVariableNames: ''!

Item was added:
+ ----- Method: SqueakAndroidStackEvtConfig>>buildType: (in category 'squeak compatibility') -----
+ buildType: aSymbol
+ 	buildType:= aSymbol!

Item was changed:
  ----- Method: SqueakAndroidStackEvtConfig>>topDir (in category 'directories') -----
  topDir
+ 		^ topDir ifNil: [ topDir := FileDirectory default directoryNamed: self oscogvm ]!
- 	^ topDir ifNil: [ topDir := FileDirectory default directoryNamed: 'oscogvm' ]!

Item was changed:
+ ----- Method: SqueakBSDCogV3Config>>buildDir (in category 'squeak compatibility') -----
- ----- Method: SqueakBSDCogV3Config>>buildDir (in category 'as yet unclassified') -----
  buildDir
  	^ buildDir ifNil: [ buildDir := ( self topDir / self buildDirName) assureExistence].!

Item was changed:
+ ----- Method: SqueakBSDCogV3Config>>buildDirName (in category 'squeak compatibility') -----
- ----- Method: SqueakBSDCogV3Config>>buildDirName (in category 'as yet unclassified') -----
  buildDirName
+ 	buildType isNil
+ 		ifTrue:[^self dirBuildPlatform, self dirBuildLanguageVMMM, 'build']
+ 		ifFalse:[^self dirBuildPlatform, self dirBuildLanguageVMMM, buildType asString]!
- 	^'cmake_build.bsd32x86/squeak.cog.v3/bld'!

Item was changed:
+ ----- Method: SqueakBSDCogV3Config>>compilerFlags (in category 'squeak compatibility') -----
- ----- Method: SqueakBSDCogV3Config>>compilerFlags (in category 'as yet unclassified') -----
  compilerFlags 
  	| releaseFlags |
  	
  	releaseFlags := self isGenerateForRelease 
  		ifTrue: [ self compilerFlagsRelease ]
  		ifFalse: [ self compilerFlagsDebug ].
  		
  	^ String streamContents: [ :stream |
  		((self commonCompilerFlags, releaseFlags)
  			asStringOn: stream 
  			delimiter: ' ' )]!

Item was changed:
+ ----- Method: SqueakBSDCogV3Config>>defaultExternalPlugins (in category 'squeak compatibility') -----
- ----- Method: SqueakBSDCogV3Config>>defaultExternalPlugins (in category 'as yet unclassified') -----
  defaultExternalPlugins
  	^ (super defaultExternalPlugins copyWithoutAll: #(#IA32ABIPlugin #ThreadedIA32FFIPlugin #InternetConfigPlugin ))
  !

Item was changed:
+ ----- Method: SqueakBSDCogV3Config>>defaultInternalPlugins (in category 'squeak compatibility') -----
- ----- Method: SqueakBSDCogV3Config>>defaultInternalPlugins (in category 'as yet unclassified') -----
  defaultInternalPlugins
  	^ (super defaultInternalPlugins copyWithoutAll: #(#IA32ABIPlugin #JoystickTabletPlugin #StarSqueakPlugin #SurfacePlugin#ThreadedIA32FFIPlugin))
  !

Item was added:
+ ----- Method: SqueakBSDCogV3Config>>dirBuildLanguageVMMM (in category 'cmake') -----
+ dirBuildLanguageVMMM
+ 	"the directory under buildPlatformDir  example: newspeak.cog.spur. use squeak.cog.v3 as default"
+ 	^self squeakCogV3!

Item was added:
+ ----- Method: SqueakBSDCogV3Config>>dirBuildPlatform (in category 'cmake') -----
+ dirBuildPlatform
+ 	"the directory for the platform. example: build.linux32x86"
+ 	^self dirBSD32x86!

Item was changed:
+ ----- Method: SqueakBSDCogV3Config>>dirFrom: (in category 'squeak compatibility') -----
- ----- Method: SqueakBSDCogV3Config>>dirFrom: (in category 'as yet unclassified') -----
  dirFrom: aStringOrDir
  	^ aStringOrDir isString
  		ifTrue: [ FileDirectory forFileName: aStringOrDir  ]
  		ifFalse: [ aStringOrDir ]!

Item was changed:
+ ----- Method: SqueakBSDCogV3Config>>executableName (in category 'squeak compatibility') -----
- ----- Method: SqueakBSDCogV3Config>>executableName (in category 'as yet unclassified') -----
  executableName
  	^ 'cogvm'!

Item was changed:
+ ----- Method: SqueakBSDCogV3Config>>outputDir (in category 'squeak compatibility') -----
- ----- Method: SqueakBSDCogV3Config>>outputDir (in category 'as yet unclassified') -----
  outputDir
  
  	"the directory where built binaries will be stored"
  	^ outputDir ifNil: [ outputDir := (self topDir / self outputDirName) ]	
  
  !

Item was changed:
+ ----- Method: SqueakBSDCogV3Config>>prepareVMMaker (in category 'squeak compatibility') -----
- ----- Method: SqueakBSDCogV3Config>>prepareVMMaker (in category 'as yet unclassified') -----
  prepareVMMaker
  	
  	| maker allPlugins |
  	
  	"In CogVMs (in contrast to Interpreter VM) the generated sources are platform independent, therefore Cross is ok"
  	maker := VMMaker forPlatform: 'Cross'.
  	
  	maker sourceDirectoryName: self srcDir pathName.
  	maker platformRootDirectoryName: self platformsDir.
  	
  	
  	allPlugins := self internalPlugins , self externalPlugins.
  	
  	"touch plugins to force their source generation unconditionally"
  	allPlugins do: [:name | (Smalltalk globals at: name) touch ].
  	
  	" Why we put all plugins as external?   Because the generated sources are not different whether the plugins were defined as internal or external. VMMaker used to need this to to generate plugins.int and plugins.ext files. But since this is achieved in another way with CMakeVMMaker, there is no different at all to put all plugins as internal or as external."
  	maker externalModules addAll:  allPlugins.
  	
  	^ maker!

Item was changed:
+ ----- Method: SqueakBSDCogV3Config>>setupDirectories: (in category 'squeak compatibility') -----
- ----- Method: SqueakBSDCogV3Config>>setupDirectories: (in category 'as yet unclassified') -----
  setupDirectories: gen
  	| dirsInclude |
  
  	" write the directories in separate include file"
  	dirsInclude := gen captureOutputDuring: [
  		gen
  			set: #topDir toString: (self topDir fullName); 
  			set: #buildDir toString: (self buildDir ifNil: ['${topDir}/build'] ifNotNil: [self buildDir fullName] );
  			set: #thirdpartyDir toString: '${buildDir}/thirdParty';
  			set: #platformsDir toString: self platformsDir;
  			set: #srcDir toString: self srcDir pathName;
  			set: #srcPluginsDir toString: (pluginsDir ifNil: [ '${srcDir}/plugins' ]);
  			set: #srcVMDir toString: '${srcDir}/vm';
  			set: #platformName toString: self platformName;
  			set: #targetPlatform to: '${platformsDir}/${platformName}';
  			set: #crossDir toString: '${platformsDir}/Cross';
  			set: #platformVMDir toString: '${targetPlatform}/vm';
  			set: #outputDir toString: self outputDir fullName.
  	].
  
  	self write: dirsInclude toFile: 'directories.cmake'.
  	
  	gen include: 'directories.cmake'.
  !

Item was changed:
+ ----- Method: SqueakBSDCogV3Config>>srcDir (in category 'squeak compatibility') -----
- ----- Method: SqueakBSDCogV3Config>>srcDir (in category 'as yet unclassified') -----
  srcDir
  		^ srcDir ifNil: [ srcDir := (self topDir directoryNamed: 'src' )]!

Item was changed:
+ ----- Method: SqueakBSDCogV3Config>>topDir (in category 'squeak compatibility') -----
- ----- Method: SqueakBSDCogV3Config>>topDir (in category 'as yet unclassified') -----
  topDir
+ 		^ topDir ifNil: [ topDir := FileDirectory default directoryNamed: self oscogvm ]!
- 	^ topDir ifNil: [ topDir := FileDirectory default directoryNamed: 'oscogvm' ]!

Item was changed:
+ ----- Method: SqueakBSDCogV3Config>>validateSourcesPresent (in category 'squeak compatibility') -----
- ----- Method: SqueakBSDCogV3Config>>validateSourcesPresent (in category 'as yet unclassified') -----
  validateSourcesPresent
  	| sources |
  	sources := Smalltalk sourcesName.
  	
  	(sources == nil)
  		ifTrue: [	self error: 'VM source code cannot be generated without .sources file'.]		!

Item was changed:
+ ----- Method: SqueakBSDCogV3Config>>write:toFile: (in category 'squeak compatibility') -----
- ----- Method: SqueakBSDCogV3Config>>write:toFile: (in category 'as yet unclassified') -----
  write: aContents toFile: aFileName
  	"write a file to current output directory (buildDir).
  	use line end convention appropriate for config platform"
  
  	| bldDir |
  	bldDir := self buildDir.
  	bldDir isString
  		ifTrue: [ bldDir := FileDirectory directoryEntryFor: bldDir ].
  	bldDir assureExistence.
  	bldDir
  		forceNewFileNamed: aFileName
  		do: [:s | s
  				nextPutAll: (self fixLineEndsOf: aContents)]
  
  !

Item was changed:
  Object subclass: #SqueakCMakeVMMakerAbstractBuilder
  	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'CMakeVMMakerSqueak-Builder'!
  
+ !SqueakCMakeVMMakerAbstractBuilder commentStamp: 'tty 6/7/2014 15:35' prior: 0!
- !SqueakCMakeVMMakerAbstractBuilder commentStamp: 'tty 6/6/2014 16:42' prior: 0!
  I am an abstract base class for various CMakeVMMakerSqueak builders.
  
  most of my methods are on class side.
  
  I am a facade to the various Squeak[Platform][WordSize][VM][MemoryManager]Config classes that provide all the functionality.
  
  Think of me as lipstick on a pig.
  
  oink!!
  
  
+ I also act as a repository of common information for the various configurations.
  
+ 
  !

Item was changed:
  ----- Method: SqueakCMakeVMMakerAbstractBuilder class>>configurationDictionary: (in category 'as yet unclassified') -----
  configurationDictionary: aCategoryName
  	"return a Dictionary of CMakeMakerSqueak-XYZ platform configurations and their associated available builds"
  	| result |
  	result := Dictionary new.
  	Smalltalk globals 
+ 		allClassesDo:[:c | (c class category asString withoutQuoting = aCategoryName)
- 		allClassesDo:[:c | (c class category asString withoutQuoting startsWith: aCategoryName)
  			ifTrue: [ result at: (c name) put:[c availableBuilds].]].
  	^result
  
  !

Item was changed:
+ ----- Method: SqueakFreeBSDCogV3Config>>buildDirName (in category 'squeak compatibility') -----
- ----- Method: SqueakFreeBSDCogV3Config>>buildDirName (in category 'as yet unclassified') -----
  buildDirName
+ 	buildType isNil
+ 		ifTrue:[^self dirBuildPlatform, self dirBuildLanguageVMMM, 'build']
+ 		ifFalse:[^self dirBuildPlatform, self dirBuildLanguageVMMM, buildType asString]!
- 	^ 'cmake_build.linux32x86/squeak.cog.v3/bld'!

Item was changed:
  CPlatformConfig subclass: #SqueakIA32BochsConfig
  	uses: TCPlatformConfigForSqueak
+ 	instanceVariableNames: 'buildType'
- 	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'CMakeVMMakerSqueak-IA32-Bochs'!
  
  !SqueakIA32BochsConfig commentStamp: 'tty 6/7/2014 10:46' prior: 0!
  A SqueakIA32BochsConfig is a Squeak Compatibility Layer between the Pharo code in CMakeVMMaker and CMakeVMakerSqueak.
  
  I exist because modifying the pharo tree is verbotten as of 2014.06.10!
  SqueakIA32BochsConfig class
  	uses: TCPlatformConfigForSqueak classTrait
  	instanceVariableNames: ''!

Item was added:
+ ----- Method: SqueakIA32BochsConfig>>buildDir (in category 'squeak compatibility') -----
+ buildDir
+ 	^ buildDir ifNil: [ buildDir := ( self topDir / self buildDirName) assureExistence].!

Item was added:
+ ----- Method: SqueakIA32BochsConfig>>buildDirName (in category 'squeak compatibility') -----
+ buildDirName
+ 	buildType isNil
+ 		ifTrue:[^self dirBuildPlatform, self dirBuildLanguageVMMM, 'build']
+ 		ifFalse:[^self dirBuildPlatform, self dirBuildLanguageVMMM, buildType asString]!

Item was added:
+ ----- Method: SqueakIA32BochsConfig>>buildType: (in category 'squeak compatibility') -----
+ buildType: aSymbol
+ 	buildType:= aSymbol!

Item was added:
+ ----- Method: SqueakIA32BochsConfig>>dirBuildLanguageVMMM (in category 'cmake') -----
+ dirBuildLanguageVMMM
+ 	"the directory under buildPlatformDir  example: newspeak.cog.spur the default is squeak.cog.v3"
+ 	^self squeakCogV3!

Item was added:
+ ----- Method: SqueakIA32BochsConfig>>dirBuildPlatform (in category 'cmake') -----
+ dirBuildPlatform
+ 	^self dirIA32Bochs!

Item was added:
+ ----- Method: SqueakIA32BochsConfig>>topDir (in category 'squeak compatibility') -----
+ topDir
+ 		^ topDir ifNil: [ topDir := FileDirectory default directoryNamed: self oscogvm ]!

Item was removed:
- SqueakCMakeVMMakerAbstractBuilder subclass: #SqueakLinuxMacOSBuilder
- 	instanceVariableNames: ''
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'CMakeVMMakerSqueak-Builder'!
- 
- !SqueakLinuxMacOSBuilder commentStamp: 'tty 6/7/2014 11:23' prior: 0!
- I am a facade.
- 
- I query, and invoke CMakeVMMakerSqueak configurations.!

Item was removed:
- ----- Method: SqueakLinuxMacOSBuilder class>>availableBuildTypesForTarget: (in category 'documentation') -----
- availableBuildTypesForTarget: aSymbol
- 	self flag:'tty'. "I do not like the hard coding of the category name. Also, how will inform kludge up auto-builds?"
- 	[
- 	((Smalltalk at: aSymbol)  category) =  (self configurationsCategory)
- 		ifTrue:[	^super availableBuildsTypesForTarget: aSymbol inCategory: ((Smalltalk at: aSymbol)  category).]
- 		ifFalse:[self inform: (self userErrorInvalidTarget: aSymbol)]
- 	] ifError:[self inform: (self userErrorInvalidTarget: aSymbol)].
- 	^nil.!

Item was removed:
- ----- Method: SqueakLinuxMacOSBuilder class>>availableTargets (in category 'documentation') -----
- availableTargets
- 	^super availableTargets: (self configurationsCategory)!

Item was removed:
- ----- Method: SqueakLinuxMacOSBuilder class>>configurationsCategory (in category 'documentation') -----
- configurationsCategory
- 	^'CMakeVMMakerSqueak-MacOS'!

Item was removed:
- SqueakCMakeVMMakerAbstractBuilder subclass: #SqueakLinuxMacOSPowerPCBuilder
- 	instanceVariableNames: ''
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'CMakeVMMakerSqueak-Builder'!
- 
- !SqueakLinuxMacOSPowerPCBuilder commentStamp: 'tty 6/7/2014 11:24' prior: 0!
- I am a facade.
- 
- I query, and invoke CMakeVMMakerSqueak configurations.!

Item was removed:
- ----- Method: SqueakLinuxMacOSPowerPCBuilder class>>availableBuildTypesForTarget: (in category 'documentation') -----
- availableBuildTypesForTarget: aSymbol
- 	self flag:'tty'. "I do not like the hard coding of the category name. Also, how will inform kludge up auto-builds?"
- 	[
- 	((Smalltalk at: aSymbol)  category) =  (self configurationsCategory)
- 		ifTrue:[	^super availableBuildsTypesForTarget: aSymbol inCategory: ((Smalltalk at: aSymbol)  category).]
- 		ifFalse:[self inform: (self userErrorInvalidTarget: aSymbol)]
- 	] ifError:[self inform: (self userErrorInvalidTarget: aSymbol)].
- 	^nil.!

Item was removed:
- ----- Method: SqueakLinuxMacOSPowerPCBuilder class>>availableTargets (in category 'documentation') -----
- availableTargets
- 	^super availableTargets: (self configurationsCategory)!

Item was removed:
- ----- Method: SqueakLinuxMacOSPowerPCBuilder class>>configurationsCategory (in category 'documentation') -----
- configurationsCategory
- 	^'CMakeVMMakerSqueak-MacOSPowerPC'!

Item was removed:
- SqueakCMakeVMMakerAbstractBuilder subclass: #SqueakLinuxMacOSX32x86Builder
- 	instanceVariableNames: ''
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'CMakeVMMakerSqueak-Builder'!
- 
- !SqueakLinuxMacOSX32x86Builder commentStamp: 'tty 6/7/2014 11:24' prior: 0!
- I am a facade.
- 
- I query, and invoke CMakeVMMakerSqueak configurations.!

Item was removed:
- ----- Method: SqueakLinuxMacOSX32x86Builder class>>availableBuildTypesForTarget: (in category 'documentation') -----
- availableBuildTypesForTarget: aSymbol
- 	self flag:'tty'. "I do not like the hard coding of the category name. Also, how will inform kludge up auto-builds?"
- 	[
- 	((Smalltalk at: aSymbol)  category) =  (self configurationsCategory)
- 		ifTrue:[	^super availableBuildsTypesForTarget: aSymbol inCategory: ((Smalltalk at: aSymbol)  category).]
- 		ifFalse:[self inform: (self userErrorInvalidTarget: aSymbol)]
- 	] ifError:[self inform: (self userErrorInvalidTarget: aSymbol)].
- 	^nil.!

Item was removed:
- ----- Method: SqueakLinuxMacOSX32x86Builder class>>availableTargets (in category 'documentation') -----
- availableTargets
- 	^super availableTargets: (self configurationsCategory)!

Item was removed:
- ----- Method: SqueakLinuxMacOSX32x86Builder class>>configurationsCategory (in category 'documentation') -----
- configurationsCategory
- 	^'CMakeVMMakerSqueak-MacOSX32x86'!

Item was removed:
- SqueakCMakeVMMakerAbstractBuilder subclass: #SqueakLinuxSunOS32x86Builder
- 	instanceVariableNames: ''
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'CMakeVMMakerSqueak-Builder'!
- 
- !SqueakLinuxSunOS32x86Builder commentStamp: 'tty 6/7/2014 11:24' prior: 0!
- I am a facade.
- 
- I query, and invoke CMakeVMMakerSqueak configurations.!

Item was removed:
- ----- Method: SqueakLinuxSunOS32x86Builder class>>availableBuildTypesForTarget: (in category 'documentation') -----
- availableBuildTypesForTarget: aSymbol
- 	self flag:'tty'. "I do not like the hard coding of the category name. Also, how will inform kludge up auto-builds?"
- 	[
- 	((Smalltalk at: aSymbol)  category) =  (self configurationsCategory)
- 		ifTrue:[	^super availableBuildsTypesForTarget: aSymbol inCategory: ((Smalltalk at: aSymbol)  category).]
- 		ifFalse:[self inform: (self userErrorInvalidTarget: aSymbol)]
- 	] ifError:[self inform: (self userErrorInvalidTarget: aSymbol)].
- 	^nil.!

Item was removed:
- ----- Method: SqueakLinuxSunOS32x86Builder class>>availableTargets (in category 'documentation') -----
- availableTargets
- 	^super availableTargets: (self configurationsCategory)!

Item was removed:
- ----- Method: SqueakLinuxSunOS32x86Builder class>>configurationsCategory (in category 'documentation') -----
- configurationsCategory
- 	^'CMakeVMMakerSqueak-SunOS32x86'!

Item was removed:
- SqueakCMakeVMMakerAbstractBuilder subclass: #SqueakLinuxSunOS32x86_64Builder
- 	instanceVariableNames: ''
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'CMakeVMMakerSqueak-Builder'!
- 
- !SqueakLinuxSunOS32x86_64Builder commentStamp: 'tty 6/7/2014 11:24' prior: 0!
- I am a facade.
- 
- I query, and invoke CMakeVMMakerSqueak configurations.!

Item was removed:
- ----- Method: SqueakLinuxSunOS32x86_64Builder class>>availableBuildTypesForTarget: (in category 'documentation') -----
- availableBuildTypesForTarget: aSymbol
- 	self flag:'tty'. "I do not like the hard coding of the category name. Also, how will inform kludge up auto-builds?"
- 	[
- 	((Smalltalk at: aSymbol)  category) =  (self configurationsCategory)
- 		ifTrue:[	^super availableBuildsTypesForTarget: aSymbol inCategory: ((Smalltalk at: aSymbol)  category).]
- 		ifFalse:[self inform: (self userErrorInvalidTarget: aSymbol)]
- 	] ifError:[self inform: (self userErrorInvalidTarget: aSymbol)].
- 	^nil.!

Item was removed:
- ----- Method: SqueakLinuxSunOS32x86_64Builder class>>availableTargets (in category 'documentation') -----
- availableTargets
- 	^super availableTargets: (self configurationsCategory)!

Item was removed:
- ----- Method: SqueakLinuxSunOS32x86_64Builder class>>configurationsCategory (in category 'documentation') -----
- configurationsCategory
- 	^'CMakeVMMakerSqueak-SunOS32x86_64'!

Item was added:
+ SqueakCMakeVMMakerAbstractBuilder subclass: #SqueakMacOSBuilder
+ 	instanceVariableNames: ''
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'CMakeVMMakerSqueak-Builder'!
+ 
+ !SqueakMacOSBuilder commentStamp: 'tty 6/7/2014 11:23' prior: 0!
+ I am a facade.
+ 
+ I query, and invoke CMakeVMMakerSqueak configurations.!

Item was added:
+ ----- Method: SqueakMacOSBuilder class>>availableBuildTypesForTarget: (in category 'documentation') -----
+ availableBuildTypesForTarget: aSymbol
+ 	self flag:'tty'. "I do not like the hard coding of the category name. Also, how will inform kludge up auto-builds?"
+ 	[
+ 	((Smalltalk at: aSymbol)  category) =  (self configurationsCategory)
+ 		ifTrue:[	^super availableBuildsTypesForTarget: aSymbol inCategory: ((Smalltalk at: aSymbol)  category).]
+ 		ifFalse:[self inform: (self userErrorInvalidTarget: aSymbol)]
+ 	] ifError:[self inform: (self userErrorInvalidTarget: aSymbol)].
+ 	^nil.!

Item was added:
+ ----- Method: SqueakMacOSBuilder class>>availableTargets (in category 'documentation') -----
+ availableTargets
+ 	^super availableTargets: (self configurationsCategory)!

Item was added:
+ ----- Method: SqueakMacOSBuilder class>>configurationsCategory (in category 'documentation') -----
+ configurationsCategory
+ 	^'CMakeVMMakerSqueak-MacOS'!

Item was changed:
  CPlatformConfig subclass: #SqueakMacOSConfig
  	uses: TCPlatformConfigForSqueak
+ 	instanceVariableNames: 'buildType'
- 	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'CMakeVMMakerSqueak-MacOS'!
  
  !SqueakMacOSConfig commentStamp: 'tty 6/7/2014 10:26' prior: 0!
  A SqueakMacOSConfig  configures a VM according to my name's form: [Operating System] [WordSize] [Processor Language][VM MemoryManager][BuildType]Conf
  !
  SqueakMacOSConfig class
  	uses: TCPlatformConfigForSqueak classTrait
  	instanceVariableNames: ''!

Item was added:
+ ----- Method: SqueakMacOSConfig>>buildDir (in category 'squeak compatibility') -----
+ buildDir
+ 	^ buildDir ifNil: [ buildDir := ( self topDir / self buildDirName) assureExistence].!

Item was added:
+ ----- Method: SqueakMacOSConfig>>buildDirName (in category 'squeak compatibility') -----
+ buildDirName
+ 	buildType isNil
+ 		ifTrue:[^self dirBuildPlatform, self dirBuildLanguageVMMM, 'build']
+ 		ifFalse:[^self dirBuildPlatform, self dirBuildLanguageVMMM, buildType asString]!

Item was added:
+ ----- Method: SqueakMacOSConfig>>buildType: (in category 'squeak compatibility') -----
+ buildType: aSymbol
+ 	buildType:= aSymbol!

Item was added:
+ ----- Method: SqueakMacOSConfig>>dirBuildLanguageVMMM (in category 'cmake') -----
+ dirBuildLanguageVMMM
+ 	"the directory under buildPlatformDir  example: newspeak.cog.spur. default is squeak.cog.v3"
+ 	^self squeakCogV3!

Item was added:
+ ----- Method: SqueakMacOSConfig>>dirBuildPlatform (in category 'cmake') -----
+ dirBuildPlatform
+ 	"the directory for the platform. example: build.linux32x86"
+ 	^self dirMacOS!

Item was added:
+ ----- Method: SqueakMacOSConfig>>topDir (in category 'squeak compatibility') -----
+ topDir
+ 		^ topDir ifNil: [ topDir := FileDirectory default directoryNamed: self oscogvm ]!

Item was added:
+ SqueakCMakeVMMakerAbstractBuilder subclass: #SqueakMacOSPowerPCBuilder
+ 	instanceVariableNames: ''
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'CMakeVMMakerSqueak-Builder'!
+ 
+ !SqueakMacOSPowerPCBuilder commentStamp: 'tty 6/7/2014 11:24' prior: 0!
+ I am a facade.
+ 
+ I query, and invoke CMakeVMMakerSqueak configurations.!

Item was added:
+ ----- Method: SqueakMacOSPowerPCBuilder class>>availableBuildTypesForTarget: (in category 'documentation') -----
+ availableBuildTypesForTarget: aSymbol
+ 	self flag:'tty'. "I do not like the hard coding of the category name. Also, how will inform kludge up auto-builds?"
+ 	[
+ 	((Smalltalk at: aSymbol)  category) =  (self configurationsCategory)
+ 		ifTrue:[	^super availableBuildsTypesForTarget: aSymbol inCategory: ((Smalltalk at: aSymbol)  category).]
+ 		ifFalse:[self inform: (self userErrorInvalidTarget: aSymbol)]
+ 	] ifError:[self inform: (self userErrorInvalidTarget: aSymbol)].
+ 	^nil.!

Item was added:
+ ----- Method: SqueakMacOSPowerPCBuilder class>>availableTargets (in category 'documentation') -----
+ availableTargets
+ 	^super availableTargets: (self configurationsCategory)!

Item was added:
+ ----- Method: SqueakMacOSPowerPCBuilder class>>configurationsCategory (in category 'documentation') -----
+ configurationsCategory
+ 	^'CMakeVMMakerSqueak-MacOSPowerPC'!

Item was changed:
  ----- Method: SqueakMacOSV3Config>>topDir (in category 'directories') -----
  topDir
+ 		^ topDir ifNil: [ topDir := FileDirectory default directoryNamed: self oscogvm ]!
- 	^ topDir ifNil: [ topDir := FileDirectory default directoryNamed: 'oscogvm' ]!

Item was added:
+ SqueakCMakeVMMakerAbstractBuilder subclass: #SqueakMacOSX32x86Builder
+ 	instanceVariableNames: ''
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'CMakeVMMakerSqueak-Builder'!
+ 
+ !SqueakMacOSX32x86Builder commentStamp: 'tty 6/7/2014 11:24' prior: 0!
+ I am a facade.
+ 
+ I query, and invoke CMakeVMMakerSqueak configurations.!

Item was added:
+ ----- Method: SqueakMacOSX32x86Builder class>>availableBuildTypesForTarget: (in category 'documentation') -----
+ availableBuildTypesForTarget: aSymbol
+ 	self flag:'tty'. "I do not like the hard coding of the category name. Also, how will inform kludge up auto-builds?"
+ 	[
+ 	((Smalltalk at: aSymbol)  category) =  (self configurationsCategory)
+ 		ifTrue:[	^super availableBuildsTypesForTarget: aSymbol inCategory: ((Smalltalk at: aSymbol)  category).]
+ 		ifFalse:[self inform: (self userErrorInvalidTarget: aSymbol)]
+ 	] ifError:[self inform: (self userErrorInvalidTarget: aSymbol)].
+ 	^nil.!

Item was added:
+ ----- Method: SqueakMacOSX32x86Builder class>>availableTargets (in category 'documentation') -----
+ availableTargets
+ 	^super availableTargets: (self configurationsCategory)!

Item was added:
+ ----- Method: SqueakMacOSX32x86Builder class>>configurationsCategory (in category 'documentation') -----
+ configurationsCategory
+ 	^'CMakeVMMakerSqueak-MacOSX32x86'!

Item was changed:
  CPlatformConfig subclass: #SqueakSunOS32x8664CogConfig
  	uses: TCPlatformConfigForSqueak
+ 	instanceVariableNames: 'buildType'
- 	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'CMakeVMMakerSqueak-SunOS32x86_64'!
  
  !SqueakSunOS32x8664CogConfig commentStamp: 'tty 6/7/2014 10:23' prior: 0!
  A SqueakSunOS32x8664CogConfig is xxxxxxxxx.
  
  
  usage: 
  SqueakSunOS32x8664CogConfig generate
  or
  SqueakSunOS32x8664CogConfig generateWithSources
  or:
  find my Builder in CMakeVMMakerSqueak-Builder category and use that to query me or invoke me!
  SqueakSunOS32x8664CogConfig class
  	uses: TCPlatformConfigForSqueak classTrait
  	instanceVariableNames: ''!

Item was added:
+ ----- Method: SqueakSunOS32x8664CogConfig>>buildDir (in category 'squeak compatibility') -----
+ buildDir
+ 	^ buildDir ifNil: [ buildDir := ( self topDir / self buildDirName) assureExistence].!

Item was added:
+ ----- Method: SqueakSunOS32x8664CogConfig>>buildDirName (in category 'squeak compatibility') -----
+ buildDirName
+ 	buildType isNil
+ 		ifTrue:[^self dirBuildPlatform, self dirBuildLanguageVMMM, 'build']
+ 		ifFalse:[^self dirBuildPlatform, self dirBuildLanguageVMMM, buildType asString]!

Item was added:
+ ----- Method: SqueakSunOS32x8664CogConfig>>buildType: (in category 'squeak compatibility') -----
+ buildType: aSymbol
+ 	buildType:= aSymbol!

Item was added:
+ ----- Method: SqueakSunOS32x8664CogConfig>>dirBuildLanguageVMMM (in category 'cmake') -----
+ dirBuildLanguageVMMM
+ 	"the directory under buildPlatformDir  example: newspeak.cog.spur. use squeak.cog.v3 as default"
+ 	^self squeakCogV3!

Item was added:
+ ----- Method: SqueakSunOS32x8664CogConfig>>dirBuildPlatform (in category 'cmake') -----
+ dirBuildPlatform
+ 	"the directory for the platform. example: build.linux32x86"
+ 	^self dirSunOS32x8664!

Item was added:
+ ----- Method: SqueakSunOS32x8664CogConfig>>topDir (in category 'squeak compatibility') -----
+ topDir
+ 		^ topDir ifNil: [ topDir := FileDirectory default directoryNamed: self oscogvm ]!

Item was added:
+ SqueakCMakeVMMakerAbstractBuilder subclass: #SqueakSunOS32x86Builder
+ 	instanceVariableNames: ''
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'CMakeVMMakerSqueak-Builder'!
+ 
+ !SqueakSunOS32x86Builder commentStamp: 'tty 6/7/2014 11:24' prior: 0!
+ I am a facade.
+ 
+ I query, and invoke CMakeVMMakerSqueak configurations.!

Item was added:
+ ----- Method: SqueakSunOS32x86Builder class>>availableBuildTypesForTarget: (in category 'documentation') -----
+ availableBuildTypesForTarget: aSymbol
+ 	self flag:'tty'. "I do not like the hard coding of the category name. Also, how will inform kludge up auto-builds?"
+ 	[
+ 	((Smalltalk at: aSymbol)  category) =  (self configurationsCategory)
+ 		ifTrue:[	^super availableBuildsTypesForTarget: aSymbol inCategory: ((Smalltalk at: aSymbol)  category).]
+ 		ifFalse:[self inform: (self userErrorInvalidTarget: aSymbol)]
+ 	] ifError:[self inform: (self userErrorInvalidTarget: aSymbol)].
+ 	^nil.!

Item was added:
+ ----- Method: SqueakSunOS32x86Builder class>>availableTargets (in category 'documentation') -----
+ availableTargets
+ 	^super availableTargets: (self configurationsCategory)!

Item was added:
+ ----- Method: SqueakSunOS32x86Builder class>>configurationsCategory (in category 'documentation') -----
+ configurationsCategory
+ 	^'CMakeVMMakerSqueak-SunOS32x86'!

Item was changed:
  CPlatformConfig subclass: #SqueakSunOS32x86CogConfig
  	uses: TCPlatformConfigForSqueak
+ 	instanceVariableNames: 'buildType'
- 	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'CMakeVMMakerSqueak-SunOS32x86'!
  
  !SqueakSunOS32x86CogConfig commentStamp: 'tty 6/7/2014 10:24' prior: 0!
  A SqueakSunOS32x86CogConfig is xxxxxxxxx.
  
  
  usage: 
  SqueakSunOS32x86CogConfig generate
  or
  SqueakSunOS32x86CogConfig generateWithSources
  or:
  find my Builder in CMakeVMMakerSqueak-Builder category and use that to query me or invoke me!
  SqueakSunOS32x86CogConfig class
  	uses: TCPlatformConfigForSqueak classTrait
  	instanceVariableNames: ''!

Item was added:
+ ----- Method: SqueakSunOS32x86CogConfig>>buildDir (in category 'squeak compatibility') -----
+ buildDir
+ 	^ buildDir ifNil: [ buildDir := ( self topDir / self buildDirName) assureExistence].!

Item was added:
+ ----- Method: SqueakSunOS32x86CogConfig>>buildDirName (in category 'squeak compatibility') -----
+ buildDirName
+ 	buildType isNil
+ 		ifTrue:[^self dirBuildPlatform, self dirBuildLanguageVMMM, 'build']
+ 		ifFalse:[^self dirBuildPlatform, self dirBuildLanguageVMMM, buildType asString]!

Item was added:
+ ----- Method: SqueakSunOS32x86CogConfig>>buildType: (in category 'squeak compatibility') -----
+ buildType: aSymbol
+ 	buildType:= aSymbol!

Item was added:
+ ----- Method: SqueakSunOS32x86CogConfig>>dirBuildLanguageVMMM (in category 'cmake') -----
+ dirBuildLanguageVMMM
+ 	"the directory under buildPlatformDir  example: newspeak.cog.spur. use squeak.cog.v3 as default"
+ 	^self squeakCogV3!

Item was added:
+ ----- Method: SqueakSunOS32x86CogConfig>>dirBuildPlatform (in category 'cmake') -----
+ dirBuildPlatform
+ 	"the directory for the platform. example: build.linux32x86"
+ 	^self dirSunOS32x86!

Item was added:
+ ----- Method: SqueakSunOS32x86CogConfig>>topDir (in category 'squeak compatibility') -----
+ topDir
+ 		^ topDir ifNil: [ topDir := FileDirectory default directoryNamed: self oscogvm ]!

Item was added:
+ SqueakCMakeVMMakerAbstractBuilder subclass: #SqueakSunOS32x86_64Builder
+ 	instanceVariableNames: ''
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'CMakeVMMakerSqueak-Builder'!
+ 
+ !SqueakSunOS32x86_64Builder commentStamp: 'tty 6/7/2014 11:24' prior: 0!
+ I am a facade.
+ 
+ I query, and invoke CMakeVMMakerSqueak configurations.!

Item was added:
+ ----- Method: SqueakSunOS32x86_64Builder class>>availableBuildTypesForTarget: (in category 'documentation') -----
+ availableBuildTypesForTarget: aSymbol
+ 	self flag:'tty'. "I do not like the hard coding of the category name. Also, how will inform kludge up auto-builds?"
+ 	[
+ 	((Smalltalk at: aSymbol)  category) =  (self configurationsCategory)
+ 		ifTrue:[	^super availableBuildsTypesForTarget: aSymbol inCategory: ((Smalltalk at: aSymbol)  category).]
+ 		ifFalse:[self inform: (self userErrorInvalidTarget: aSymbol)]
+ 	] ifError:[self inform: (self userErrorInvalidTarget: aSymbol)].
+ 	^nil.!

Item was added:
+ ----- Method: SqueakSunOS32x86_64Builder class>>availableTargets (in category 'documentation') -----
+ availableTargets
+ 	^super availableTargets: (self configurationsCategory)!

Item was added:
+ ----- Method: SqueakSunOS32x86_64Builder class>>configurationsCategory (in category 'documentation') -----
+ configurationsCategory
+ 	^'CMakeVMMakerSqueak-SunOS32x86_64'!

Item was changed:
  CPlatformConfig subclass: #SqueakWin32x86CogFamilyConfig
  	uses: TCPlatformConfigForSqueak
+ 	instanceVariableNames: 'buildType'
- 	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'CMakeVMMakerSqueak-Win32x86'!
  
  !SqueakWin32x86CogFamilyConfig commentStamp: '<historical>' prior: 0!
  This is an abstract class and it is the root configuration for building all types of Cog VMs on MS-Windows platform.
  
  
  What you need to get started:
  
  Download and install Msys, with C/C++ compiler support:
  	http://www.mingw.org/wiki/msys
  	
  Download and install Git:
  	http://code.google.com/p/msysgit/
  	
  
  ///
  Optional: add git to the PATH variable:
  
  Add path to git for msys:
  Control panel -> System -> System Properies / Advanced  [ Environment Variables ]
  
  There should be already:
  C:\Program Files\Git\cmd
  
  add:
  
  C:\Program Files\Git\bin
  
  /// For automated builds, add SQUEAKVM environment variable and set it to the full path to squeak executable.
  
  (Control panel -> System -> System Properies / Advanced  [ Environment Variables ])
  
  in windows shell you can use it then to run squeak: %SQUEAKVM%  , and in mingw bash shell, use $SQUEAKVM
  
  /// Install CMake:
  http://www.cmake.org/cmake/resources/software.html
  
  (during installation, in install options , make sure that you choose to add CMake to PATH)
  
  
  Note, to run cmake under msys shell, you have to explicitly specify the msys makefiles generator, because default one is MS:
  
  cmake . -G"MSYS Makefiles"
  
  
  Fore more information, check the class comments of all the superclasses.
  !
  SqueakWin32x86CogFamilyConfig class
  	uses: TCPlatformConfigForSqueak classTrait
  	instanceVariableNames: ''!

Item was changed:
  ----- Method: SqueakWin32x86CogFamilyConfig>>buildDirName (in category 'directories') -----
  buildDirName
+ 	buildType isNil
+ 		ifTrue:[^self dirBuildPlatform, self dirBuildLanguageVMMM, 'build']
+ 		ifFalse:[^self dirBuildPlatform, self dirBuildLanguageVMMM, buildType asString]!
- 	^ 'cmake_cygwinbuild'!

Item was added:
+ ----- Method: SqueakWin32x86CogFamilyConfig>>buildType: (in category 'squeak compatibility') -----
+ buildType: aSymbol
+ 	buildType:=aSymbol!

Item was added:
+ ----- Method: SqueakWin32x86CogFamilyConfig>>dirBuildLanguageVMMM (in category 'cmake') -----
+ dirBuildLanguageVMMM
+ 	"the directory under buildPlatformDir  example: newspeak.cog.spur. use squeak.cog.v3 as default"
+ 	^self squeakCogV3!

Item was added:
+ ----- Method: SqueakWin32x86CogFamilyConfig>>dirBuildPlatform (in category 'cmake') -----
+ dirBuildPlatform
+ 	"the directory for the platform. example: build.linux32x86"
+ 	^self dirWin32x86!

Item was changed:
  ----- Method: SqueakWin32x86CogFamilyConfig>>topDir (in category 'directories') -----
  topDir
+ 		^ topDir ifNil: [ topDir := FileDirectory default directoryNamed: self oscogvm ]!
- 	^ topDir ifNil: [ topDir := FileDirectory default directoryNamed: 'oscogvm' ]!

Item was changed:
  ----- Method: TCPlatformConfigForSqueak>>buildDir (in category 'squeak compatibility') -----
  buildDir
  	self required!

Item was added:
+ ----- Method: TCPlatformConfigForSqueak>>buildType: (in category 'squeak compatibility') -----
+ buildType: aSymbol
+ 	self required!

Item was added:
+ ----- Method: TCPlatformConfigForSqueak>>dirBSD32x86 (in category 'cmake') -----
+ dirBSD32x86
+ 	^'cmake_build.bsd32x86'!

Item was added:
+ ----- Method: TCPlatformConfigForSqueak>>dirBuild (in category 'cmake') -----
+ dirBuild
+ 	^'build'!

Item was added:
+ ----- Method: TCPlatformConfigForSqueak>>dirBuildAssert (in category 'cmake') -----
+ dirBuildAssert
+ 	^'build.assert'!

Item was added:
+ ----- Method: TCPlatformConfigForSqueak>>dirBuildDebug (in category 'cmake') -----
+ dirBuildDebug
+ 	^'build.debug'!

Item was added:
+ ----- Method: TCPlatformConfigForSqueak>>dirBuildDebugITimerHeartbeat (in category 'cmake') -----
+ dirBuildDebugITimerHeartbeat
+ 	^'build.debug.itimerheartbeat'!

Item was added:
+ ----- Method: TCPlatformConfigForSqueak>>dirBuildITimerHeartbeat (in category 'cmake') -----
+ dirBuildITimerHeartbeat
+ 	^'build.itimerheartbeat'!

Item was added:
+ ----- Method: TCPlatformConfigForSqueak>>dirBuildLanguageVMMM (in category 'cmake') -----
+ dirBuildLanguageVMMM
+ 	"the directory under buildPlatformDir  example: newspeak.cog.spur. use squeak.cog.v3 as default"
+ 	self required!

Item was added:
+ ----- Method: TCPlatformConfigForSqueak>>dirBuildPlatform (in category 'cmake') -----
+ dirBuildPlatform
+ 	"the directory for the platform. example: build.linux32x86"
+ 	self required!

Item was added:
+ ----- Method: TCPlatformConfigForSqueak>>dirIA32Bochs (in category 'cmake') -----
+ dirIA32Bochs
+ 	^'cmake_build.ia32bochs'!

Item was added:
+ ----- Method: TCPlatformConfigForSqueak>>dirIOS (in category 'cmake') -----
+ dirIOS
+ 	^'cmake_build.ios'!

Item was added:
+ ----- Method: TCPlatformConfigForSqueak>>dirLinux32Armv6 (in category 'cmake') -----
+ dirLinux32Armv6
+ 	^'cmake_build.linux32armv6'!

Item was added:
+ ----- Method: TCPlatformConfigForSqueak>>dirLinux32x86 (in category 'cmake') -----
+ dirLinux32x86
+ 	^'cmake_build.linux32x86'!

Item was added:
+ ----- Method: TCPlatformConfigForSqueak>>dirLinux32x8664 (in category 'cmake') -----
+ dirLinux32x8664
+ 	^'cmake_build.linux32x86_64'!

Item was added:
+ ----- Method: TCPlatformConfigForSqueak>>dirMacOS (in category 'cmake') -----
+ dirMacOS
+ 	^'cmake_build.macos'!

Item was added:
+ ----- Method: TCPlatformConfigForSqueak>>dirMacOSPowerPC (in category 'cmake') -----
+ dirMacOSPowerPC
+ 	^'cmake_build.macospowerpc'!

Item was added:
+ ----- Method: TCPlatformConfigForSqueak>>dirMacOSX32x86 (in category 'cmake') -----
+ dirMacOSX32x86
+ 	^'cmake_build.macosx32x86'!

Item was added:
+ ----- Method: TCPlatformConfigForSqueak>>dirSunOS32x86 (in category 'cmake') -----
+ dirSunOS32x86
+ 	^'cmake_build.sunos32x86'!

Item was added:
+ ----- Method: TCPlatformConfigForSqueak>>dirSunOS32x8664 (in category 'cmake') -----
+ dirSunOS32x8664
+ 	^'cmake_build.sunos32x86_64'!

Item was added:
+ ----- Method: TCPlatformConfigForSqueak>>dirWin32x86 (in category 'cmake') -----
+ dirWin32x86
+ 	^'cmake_build.win32x86'!

Item was added:
+ ----- Method: TCPlatformConfigForSqueak>>newspeakCogSpur (in category 'cmake') -----
+ newspeakCogSpur
+ 	^'newspeak.cog.spur'!

Item was added:
+ ----- Method: TCPlatformConfigForSqueak>>newspeakCogV3 (in category 'cmake') -----
+ newspeakCogV3
+ 	^'newspeak.cog.v3'!

Item was added:
+ ----- Method: TCPlatformConfigForSqueak>>newspeakSistaSpur (in category 'cmake') -----
+ newspeakSistaSpur
+ 	^'newspeak.sista.Spur'!

Item was added:
+ ----- Method: TCPlatformConfigForSqueak>>newspeakSistaV3 (in category 'cmake') -----
+ newspeakSistaV3
+ 	^'newspeak.sista.v3'!

Item was added:
+ ----- Method: TCPlatformConfigForSqueak>>newspeakStackSpur (in category 'cmake') -----
+ newspeakStackSpur
+ 	^'newspeak.stack.spur'!

Item was added:
+ ----- Method: TCPlatformConfigForSqueak>>newspeakStackV3 (in category 'cmake') -----
+ newspeakStackV3
+ 	^'newspeak.stack.v3'!

Item was added:
+ ----- Method: TCPlatformConfigForSqueak>>oscogvm (in category 'cmake') -----
+ oscogvm
+ 	^'oscogvm'!

Item was added:
+ ----- Method: TCPlatformConfigForSqueak>>squeakCogSpur (in category 'cmake') -----
+ squeakCogSpur
+ 	^'squeak.cog.spur'!

Item was added:
+ ----- Method: TCPlatformConfigForSqueak>>squeakCogV3 (in category 'cmake') -----
+ squeakCogV3
+ 	^'squeak.cog.v3'!

Item was added:
+ ----- Method: TCPlatformConfigForSqueak>>squeakSistaSpur (in category 'cmake') -----
+ squeakSistaSpur
+ 	^'squeak.sista.Spur'!

Item was added:
+ ----- Method: TCPlatformConfigForSqueak>>squeakSistaV3 (in category 'cmake') -----
+ squeakSistaV3
+ 	^'squeak.sista.v3'!

Item was added:
+ ----- Method: TCPlatformConfigForSqueak>>squeakStackSpur (in category 'cmake') -----
+ squeakStackSpur
+ 	^'squeak.stack.spur'!

Item was added:
+ ----- Method: TCPlatformConfigForSqueak>>squeakStackV3 (in category 'cmake') -----
+ squeakStackV3
+ 	^'squeak.stack.v3'!

Item was changed:
  CPlatformConfig subclass: #Win32x86NewspeakCogV3Config
  	uses: TCPlatformConfigForSqueak
+ 	instanceVariableNames: 'buildType'
- 	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'CMakeVMMakerSqueak-Win32x86'!
  
  !Win32x86NewspeakCogV3Config commentStamp: 'tty 6/7/2014 10:22' prior: 0!
  I configure a VM according to my name's form: [Operating System] [WordSize] [Processor Language][VM MemoryManager][BuildType]Conf
  
  
  !
  Win32x86NewspeakCogV3Config class
  	uses: TCPlatformConfigForSqueak classTrait
  	instanceVariableNames: ''!

Item was added:
+ ----- Method: Win32x86NewspeakCogV3Config>>buildDir (in category 'squeak compatibility') -----
+ buildDir
+ 	^ buildDir ifNil: [ buildDir := ( self topDir / self buildDirName) assureExistence].!

Item was added:
+ ----- Method: Win32x86NewspeakCogV3Config>>buildDirName (in category 'squeak compatibility') -----
+ buildDirName
+ 	buildType isNil
+ 		ifTrue:[^self dirBuildPlatform, self dirBuildLanguageVMMM, 'build']
+ 		ifFalse:[^self dirBuildPlatform, self dirBuildLanguageVMMM, buildType asString]!

Item was added:
+ ----- Method: Win32x86NewspeakCogV3Config>>buildType: (in category 'squeak compatibility') -----
+ buildType: aSymbol
+ 	buildType:= aSymbol!

Item was added:
+ ----- Method: Win32x86NewspeakCogV3Config>>dirBuildLanguageVMMM (in category 'cmake') -----
+ dirBuildLanguageVMMM
+ 	"the directory under buildPlatformDir  example: newspeak.cog.spur. use squeak.cog.v3 as default"
+ 	^self squeakCogV3!

Item was added:
+ ----- Method: Win32x86NewspeakCogV3Config>>dirBuildPlatform (in category 'cmake') -----
+ dirBuildPlatform
+ 	"the directory for the platform. example: build.linux32x86"
+ 	^self dirWin32x86!

Item was added:
+ ----- Method: Win32x86NewspeakCogV3Config>>topDir (in category 'squeak compatibility') -----
+ topDir
+ 		^ topDir ifNil: [ topDir := FileDirectory default directoryNamed: self oscogvm ]!

Item was changed:
  CPlatformConfig subclass: #Win32x86NewspeakStackV3Config
  	uses: TCPlatformConfigForSqueak
+ 	instanceVariableNames: 'buildType'
- 	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'CMakeVMMakerSqueak-Win32x86'!
  
  !Win32x86NewspeakStackV3Config commentStamp: 'tty 6/7/2014 10:22' prior: 0!
  I configure a VM according to my name's form: [Operating System] [WordSize] [Processor Language][VM MemoryManager][BuildType]Conf
  
  
  !
  Win32x86NewspeakStackV3Config class
  	uses: TCPlatformConfigForSqueak classTrait
  	instanceVariableNames: ''!

Item was added:
+ ----- Method: Win32x86NewspeakStackV3Config>>buildDir (in category 'squeak compatibility') -----
+ buildDir
+ 	^ buildDir ifNil: [ buildDir := ( self topDir / self buildDirName) assureExistence].!

Item was added:
+ ----- Method: Win32x86NewspeakStackV3Config>>buildDirName (in category 'squeak compatibility') -----
+ buildDirName
+ 	buildType isNil
+ 		ifTrue:[^self dirBuildPlatform, self dirBuildLanguageVMMM, 'build']
+ 		ifFalse:[^self dirBuildPlatform, self dirBuildLanguageVMMM, buildType asString]!

Item was added:
+ ----- Method: Win32x86NewspeakStackV3Config>>buildType: (in category 'squeak compatibility') -----
+ buildType: aSymbol
+ 	buildType:= aSymbol!

Item was added:
+ ----- Method: Win32x86NewspeakStackV3Config>>dirBuildLanguageVMMM (in category 'cmake') -----
+ dirBuildLanguageVMMM
+ 	"the directory under buildPlatformDir  example: newspeak.cog.spur. use squeak.cog.v3 as default"
+ 	^self squeakStackV3!

Item was added:
+ ----- Method: Win32x86NewspeakStackV3Config>>dirBuildPlatform (in category 'cmake') -----
+ dirBuildPlatform
+ 	"the directory for the platform. example: build.linux32x86"
+ 	^self dirWin32x86!

Item was added:
+ ----- Method: Win32x86NewspeakStackV3Config>>topDir (in category 'squeak compatibility') -----
+ topDir
+ 		^ topDir ifNil: [ topDir := FileDirectory default directoryNamed: self oscogvm ]!

Item was changed:
  CPlatformConfig subclass: #Win32x86SqueakCogSpurConfig
  	uses: TCPlatformConfigForSqueak
+ 	instanceVariableNames: 'buildType'
- 	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'CMakeVMMakerSqueak-Win32x86'!
  
  !Win32x86SqueakCogSpurConfig commentStamp: 'tty 6/7/2014 10:22' prior: 0!
  I configure a VM according to my name's form: [Operating System] [WordSize] [Processor Language][VM MemoryManager][BuildType]Conf
  
  
  !
  Win32x86SqueakCogSpurConfig class
  	uses: TCPlatformConfigForSqueak classTrait
  	instanceVariableNames: ''!

Item was added:
+ ----- Method: Win32x86SqueakCogSpurConfig>>buildDir (in category 'squeak compatibility') -----
+ buildDir
+ 	^ buildDir ifNil: [ buildDir := ( self topDir / self buildDirName) assureExistence].!

Item was added:
+ ----- Method: Win32x86SqueakCogSpurConfig>>buildDirName (in category 'squeak compatibility') -----
+ buildDirName
+ 	buildType isNil
+ 		ifTrue:[^self dirBuildPlatform, self dirBuildLanguageVMMM, 'build']
+ 		ifFalse:[^self dirBuildPlatform, self dirBuildLanguageVMMM, buildType asString]!

Item was added:
+ ----- Method: Win32x86SqueakCogSpurConfig>>buildType: (in category 'squeak compatibility') -----
+ buildType: aSymbol
+ 	buildType:= aSymbol!

Item was added:
+ ----- Method: Win32x86SqueakCogSpurConfig>>dirBuildLanguageVMMM (in category 'cmake') -----
+ dirBuildLanguageVMMM
+ 	"the directory under buildPlatformDir  example: newspeak.cog.spur. use squeak.cog.v3 as default"
+ 	^self squeakCogSpur!

Item was added:
+ ----- Method: Win32x86SqueakCogSpurConfig>>dirBuildPlatform (in category 'cmake') -----
+ dirBuildPlatform
+ 	"the directory for the platform. example: build.linux32x86"
+ 	^self dirWin32x86!

Item was added:
+ ----- Method: Win32x86SqueakCogSpurConfig>>topDir (in category 'squeak compatibility') -----
+ topDir
+ 		^ topDir ifNil: [ topDir := FileDirectory default directoryNamed: self oscogvm ]!

Item was changed:
  CPlatformConfig subclass: #Win32x86SqueakStackSpurConfig
  	uses: TCPlatformConfigForSqueak
+ 	instanceVariableNames: 'buildType'
- 	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'CMakeVMMakerSqueak-Win32x86'!
  
  !Win32x86SqueakStackSpurConfig commentStamp: 'tty 6/7/2014 10:20' prior: 0!
  I configure a VM according to my name's form: [Operating System] [WordSize] [Processor Language][VM MemoryManager][BuildType]Conf
  
  !
  Win32x86SqueakStackSpurConfig class
  	uses: TCPlatformConfigForSqueak classTrait
  	instanceVariableNames: ''!

Item was added:
+ ----- Method: Win32x86SqueakStackSpurConfig>>buildDir (in category 'squeak compatibility') -----
+ buildDir
+ 	^ buildDir ifNil: [ buildDir := ( self topDir / self buildDirName) assureExistence].!

Item was added:
+ ----- Method: Win32x86SqueakStackSpurConfig>>buildDirName (in category 'squeak compatibility') -----
+ buildDirName
+ 	buildType isNil
+ 		ifTrue:[^self dirBuildPlatform, self dirBuildLanguageVMMM, 'build']
+ 		ifFalse:[^self dirBuildPlatform, self dirBuildLanguageVMMM, buildType asString]!

Item was added:
+ ----- Method: Win32x86SqueakStackSpurConfig>>buildType: (in category 'squeak compatibility') -----
+ buildType: aSymbol
+ 	buildType:= aSymbol!

Item was added:
+ ----- Method: Win32x86SqueakStackSpurConfig>>dirBuildLanguageVMMM (in category 'cmake') -----
+ dirBuildLanguageVMMM
+ 	"the directory under buildPlatformDir  example: newspeak.cog.spur. use squeak.cog.v3 as default"
+ 	^self squeakStackSpur!

Item was added:
+ ----- Method: Win32x86SqueakStackSpurConfig>>dirBuildPlatform (in category 'cmake') -----
+ dirBuildPlatform
+ 	"the directory for the platform. example: build.linux32x86"
+ 	^self dirWin32x86!

Item was added:
+ ----- Method: Win32x86SqueakStackSpurConfig>>topDir (in category 'squeak compatibility') -----
+ topDir
+ 		^ topDir ifNil: [ topDir := FileDirectory default directoryNamed: self oscogvm ]!

Item was added:
+ ----- Method: Win32x86SqueakStackV3Config>>dirBuildLanguageVMMM (in category 'cmake') -----
+ dirBuildLanguageVMMM
+ 	"the directory under buildPlatformDir  example: newspeak.cog.spur. use squeak.cog.v3 as default"
+ 	^self squeakStackV3!



More information about the Vm-dev mailing list