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

commits at source.squeak.org commits at source.squeak.org
Sat Jun 18 18:19:50 UTC 2016


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

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

Name: CMakeVMMakerSqueak-tty.125
Author: tty
Time: 18 June 2016, 1:24:08.924628 pm
UUID: 5aebcc78-d7e1-4b52-8c70-2251899215cb
Ancestors: CMakeVMMakerSqueak-tty.124

Decoupled CMakeVMMakerSqueak from CMakeVMMaker.

All tests pass, output generated.

Next Up:
Build a 64x64 squeak.cog.spur Configuration.
Update/verify Help Tutorial accurately reflects process.
Debug CMake errors that popped up with Ian's TestBigEndian macro:
 
CMake Error at /usr/share/cmake-2.8/Modules/TestBigEndian.cmake:44 (message):
  no suitable type found
Call Stack (most recent call first):
  config.cmake:40 (TEST_BIG_ENDIAN)
  CMakeLists.txt:162 (include)

=============== Diff against CMakeVMMakerSqueak-tty.124 ===============

Item was changed:
  SystemOrganization addCategory: #CMakeVMMakerSqueak!
  SystemOrganization addCategory: #'CMakeVMMakerSqueak-BSD32x86'!
  SystemOrganization addCategory: #'CMakeVMMakerSqueak-Builder'!
  SystemOrganization addCategory: #'CMakeVMMakerSqueak-CMakeCompositeTemplates'!
  SystemOrganization addCategory: #'CMakeVMMakerSqueak-CMakeCustomTemplates'!
  SystemOrganization addCategory: #'CMakeVMMakerSqueak-CMakeTemplates'!
  SystemOrganization addCategory: #'CMakeVMMakerSqueak-Help'!
  SystemOrganization addCategory: #'CMakeVMMakerSqueak-IA32-Bochs'!
  SystemOrganization addCategory: #'CMakeVMMakerSqueak-IOS'!
- SystemOrganization addCategory: #'CMakeVMMakerSqueak-Libs'!
  SystemOrganization addCategory: #'CMakeVMMakerSqueak-Linux32ARMv6'!
  SystemOrganization addCategory: #'CMakeVMMakerSqueak-Linux32x86'!
  SystemOrganization addCategory: #'CMakeVMMakerSqueak-Linux64X86-32BitCompatibility'!
  SystemOrganization addCategory: #'CMakeVMMakerSqueak-Linux64x64'!
  SystemOrganization addCategory: #'CMakeVMMakerSqueak-MacOSPowerPC'!
  SystemOrganization addCategory: #'CMakeVMMakerSqueak-MacOSX32x86'!
  SystemOrganization addCategory: #'CMakeVMMakerSqueak-SunOS32x86'!
  SystemOrganization addCategory: #'CMakeVMMakerSqueak-Tests'!
  SystemOrganization addCategory: #'CMakeVMMakerSqueak-VMPlugins'!
  SystemOrganization addCategory: #'CMakeVMMakerSqueak-Win32x86'!

Item was changed:
  ----- Method: CMakeVMGeneratorForSqueak>>generateByTemplate (in category 'code generation') -----
  generateByTemplate
  	"The bulk of CMake generation happens here.
  	
  	See CPlatformConfigForSqueak>>initialize for CMake output. that occurs prior to this method. (This may change on refactoring)
  
  	Think Seaside renderOn composition.
  	"
  	| extPlugins intPlugins |
  	self flag: 'tty'. "refactor so that the cascade reflects CMake terminilogy"
  	output := String new writeStream.
  	config templates: OrderedCollection new. 
  	config 
  		setGlobalOptions: self;    
  		cmakePrefixPath;
  		cmakeIncludePath;
  		cmakeLibraryPath;
  		cmakeIncludeModules;
  		cmakeCFlags;          
  		cmakeAddDefinitions;
  		cmakeWriteDirectoriesDotCmake:  self;
  		cmakeIncludeDirectories:  self;   "<---"
  		preferredIncludes;                      "<---why 3  of em?"
  		standardIncludes;                       "<---"
  		setGlobalOptionsAfterDetermineSystem: self;    
  		extraVMSettings: self;                "<--catch-all method. os/platform specific"
  		setCoreSources: self;
  		setPlatformSources: self;
  		setCrossSources: self;
  		setExtraSources;
  		cmakeSetSourceFilesProperties;
  		cmakeListAppend:'LINKLIBS' elements: (config externalLibs);
  		cmakeAddExecutableNameOptionSource: self;
  	      setExecutableOutputPath;
  		addVMPlugins: self.
  	config templates do: [:each | self puts: each content].
  	config templates: OrderedCollection new. 
  	extPlugins := self generatePluginConfigs: config internalPlugins internal: true.
  	 intPlugins := self generatePluginConfigs: config externalPlugins internal: false.
+ 	self flag:'tty: pharo code would download and install libraries. I think detection belongs in CMake and user should set up their own system for squeak. '.
+ "	self processThirdpartyLibraries.       "
- 	self processThirdpartyLibraries.                       "<--unused in Pharo code? What exactly does this do?"
  	self processPlugins:  intPlugins, extPlugins.
  	self config templates	addLast:((CMakeCommand new) command:'target_link_libraries' params:(self moduleName , ' ${LINKLIBS}')).
  "	self cmd: 'target_link_libraries'
  		params: self moduleName , ' ${LINKLIBS}'."
  	config postBuildActions: self..
  	config templates do: [:each | self puts: each content].
  	self saveFile.
  	self generateBuildScript!

Item was removed:
- ----- Method: CMakeVMMakerSqueakCommonConfigTest>>testCommonCompilerFlags (in category 'as yet unclassified') -----
- testCommonCompilerFlags
- 	#(#SqueakMacintoshConfig #SqueakUnixConfig #SqueakWindowsConfig) 
- 		do:[:each | 
- 			(Smalltalk at:each) 
- 				allSubclassesDo:[:configuration | | o |
- 					configuration isAbstractBaseClass   "*"
- 					ifFalse:[	o:= configuration basicNew. 
- 							self assert:(o commonCompilerFlags isKindOf: Collection)]]].
- 
- "*
- SqueakWin32x86Config browse
- the return array embeds 'self executableName' which does not exist in an AbstractBaseClass
- "
- 
- 
- 
- 
- 
- 
- 
- !

Item was added:
+ ----- Method: CMakeVMMakerSqueakCommonConfigTest>>testIsLittleEndian (in category 'as yet unclassified') -----
+ testIsLittleEndian
+ 	#(#SqueakMacintoshConfig #SqueakUnixConfig #SqueakWindowsConfig) 
+ 		do:[:each | 
+ 			(Smalltalk at:each) 
+ 				allSubclassesDo:[:configuration | | o |
+ 					configuration isAbstractBaseClass not
+ 						ifTrue:[
+ 							o:= configuration basicNew.
+ 							(o excludeFromBuild not)
+ 								ifTrue:[	self assert:(o  isLittleEndian)]]]]
+ 
+ 
+ 
+ 
+ 
+ 
+ 
+ !

Item was removed:
- ----- Method: CMakeVMMakerSqueakRedirectMethodsTest>>testCommonCompilerFlags (in category 'as yet unclassified') -----
- testCommonCompilerFlags
- 	#(#SqueakMacintoshConfig #SqueakUnixConfig #SqueakWindowsConfig ) 
- 		do:[:each | 
- 			(Smalltalk at:each) 
- 				allSubclassesDo:[:configuration | | o buildTypes|
- 					o:= configuration basicNew.
- 					(o excludeFromBuild not) & (configuration isAbstractBaseClass not)
- 						ifTrue:[
- 							buildTypes:=o availableBuildTypes copyWithoutAll:#(#buildNone).
- 							buildTypes do:[:buildType |
- 								o configureForBuildType: buildType.
- 								self assert:(o  commonCompilerFlags isArray)]]]].
- !

Item was removed:
- ----- Method: CMakeVMMakerSqueakRedirectMethodsTest>>testThirdPartyLibs (in category 'as yet unclassified') -----
- testThirdPartyLibs
- 	#(#SqueakMacintoshConfig #SqueakUnixConfig #SqueakWindowsConfig ) 
- 		do:[:each | 
- 			(Smalltalk at:each) 
- 				allSubclassesDo:[:configuration | | o buildTypes|
- 					o:= configuration basicNew.
- 					(o excludeFromBuild not) & (configuration isAbstractBaseClass not)
- 						ifTrue:[
- 							buildTypes:=o availableBuildTypes copyWithoutAll:#(#buildNone).
- 							buildTypes do:[:buildType |
- 								o configureForBuildType: buildType.
- 								self assert:(o  thirdpartyLibs isKindOf: Collection).
- 								]]]].
- 
- 
- 
- 
- 
- 
- 
- !

Item was removed:
- ----- Method: CMakeVMMakerSqueakRedirectMethodsWithArgTest>>testSetExtraTargetProperties (in category 'as yet unclassified') -----
- testSetExtraTargetProperties
- 	self flag:'tty'. "Is the self shouldnt sufficient?"
- 	#(#SqueakMacintoshConfig #SqueakUnixConfig #SqueakWindowsConfig ) 
- 		do:[:each | 
- 			(Smalltalk at:each) 
- 				allSubclassesDo:[:configuration | | o buildTypes vmGenerator|
- 					o:= configuration basicNew.
- 					(o excludeFromBuild not) & (configuration isAbstractBaseClass not)
- 						ifTrue:[
- 							buildTypes:=o availableBuildTypes copyWithoutAll:#(#buildNone).
- 							buildTypes do:[:buildType |
- 								o configureForBuildType: buildType.
- 								vmGenerator:=CMakeVMGeneratorForSqueak new.
- 								vmGenerator config: o.
- 								vmGenerator output:(String new writeStream).
- 								self shouldnt: [o setExtraTargetProperties: vmGenerator] raise: Error]]]].
- !

Item was changed:
  ----- Method: CMakeVMMakerSqueakTutorialNewConfigurationHelp class>>pages (in category 'accessing') -----
  pages
  
  "platformSources...cogitClass...src vs vmsrc"
  	^#(
  overview 
  tests 
  identifyPlatform 
  identifyPlatformAbstractBaseClass
  identifyBuilder
  createTheConfiguration
  excludingConfigFromBuilds
  setAvailableBuildTypes
  firstCMakeGeneration
  tackingStockOne
  cPlatformConfigForSqueak
  methodRedirectPattern
  theVMGenerator
  tackingStockTwo
  cPlatformConfigForSqueakInitialize
  initializePlatformSources
  customizePlatformSources
  initializeVMPlugins
  customizeVMPlugins
  configGenerateByTemplate
  specifyCogitClass
  
  vmsrc
  
  specifyDirectories
  dirBuildLanguageVMMM
  setGlobalOptions
  cmakePrefixPath
  cmakeIncludePath
  cmakeLibraryPath
  cmakeIncludeModules
  cmakeCFlags
  cmakeAddDefinitions
  cmakeWriteDirectoriesDotCmake
  cmakeIncludeDirectories
  preferredIncludes
  standardIncludes
  setGlobalOptionsAfterDetermineSystem
  extraVMSettings
  setCoreSources
  setPlatformSources
  setCrossSources
  setExtraSources
  cmakeSetSourceFilesProperties
  cmakeListAppendLINKLIBSelements
  cmakeAddExecutableNameOptionSource
  setExecutableOutputPath
  addVMPlugins
  generatePluginConfigs
  specifyPlugins
- processThirdpartyLibraries
  processPlugins
  postBuildActions
  generateBuildScript
  fin
  )
  
  !

Item was removed:
- ----- Method: CMakeVMMakerSqueakTutorialNewConfigurationHelp class>>processThirdpartyLibraries (in category 'pages') -----
- processThirdpartyLibraries
- 	^HelpTopic
- 		title:'Process Third Party Libraries'
- 		contents:
- 'Within the broad outline of this tutorial, you are here: 
- 8. Customizing your Configuration.
- 
- SystemNavigation browseAllImplementorsOf: #processThirdpartyLibraries
- 
- I have no idea what this does. It exists in the pharo codebase. 
- 
- If I do figure out its utility, then the processing architecture will be similar or identical to the Plugin processing.
- 
- i.e. Libraries will be represented by objects which will have the responsibility of generating ''stuff''.
- 
- 
- 
- .'!

Item was changed:
+ Object subclass: #CPlatformConfigForSqueak
- CPlatformConfig subclass: #CPlatformConfigForSqueak
  	instanceVariableNames: 'buildType cogDir generateBuild generateBuildAssert generateBuildAssertITimerHeartbeat generateBuildDebug generateBuildDebugITimerHeartbeat generateBuildDebugMultiThreaded generateBuildIHeartbeatTimer generateBuildMultiThreaded generateBuildMultiThreadedAssert generateBuildMultiThreadedDebug templates enabledebugmessages platformSources vmplugins'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'CMakeVMMakerSqueak'!
  CPlatformConfigForSqueak class
  	instanceVariableNames: 'isAbstractBaseClass'!
  
  !CPlatformConfigForSqueak commentStamp: 'tty 12/8/2014 11:28' prior: 0!
  A CPlatformConfigForSqueak acts as a compatability layer for Squeak and an Abstract Base Class for extended functionality required for the Squeak CMakeVMMaker use-case.
  
  I make (very) heavy use of a specific design pattern for configuring myself and remaining compatible with pharo's CMakeVMMaker.
  The entry point for that pattern is my method 'configureForBuildType: aSymbol' . Each method send in there detects my buildType and routes the send
  to the approriate method for that buildType.
  
  Subclasses of me 'must' configure themselves for each build type per that pattern. 
  However this can be very easy by just returning the base configuration.
  
  Tests are written to verify that this support infrastructure is in place.
  
  I have two important methods.
  
  excludeFromBuild and isAbstractBaseClass.
  
  excludeFromBuild 
  		is used to exclude a configuration from being built by a Builder.
  		is used to exclude a configuration from Testing.
  
  isAbstractBaseClass 
  		is used by configurations that exclude themselves from being built by a Builder BUT need to be included in 		Testing.
  
  										
  excludeFromBuild  | isAbstractBaseClass  | should build  | should test
  	T					    T                            NO                  YES
        T					    F                             NO                   NO
        F					    T                            YES                  YES
        F                                 F                            YES                  YES
  
  
  The use-case is as follows.
  
  An abstract base class contains a lot of functionality that must be implemented and tested for the system to work, but it is not meant to be compiled.
  
  concrete classes of that AbstractBase class can exclude themselves from being built by builders and by doing so are not tested.
  However, once a concrete configuration is enabled to be built, it must pass all tests.
  
  Linux32x86Config is an example of an AbstractBase class that must pass all testing, but is not buildable.
  Its subclass Linux32x86SqueakCogV3Config needs testing, but a developer can toggle 'exclude from build' to hide it from Builders or make it available to them.
  
  Tests make the decision on what configurations to test. Here are some examples.
  	(o excludeFromBuild not) & (configuration isAbstractBaseClass not)  this is a concrete [Lang][VM][MemoryManager][etc] configuration that will be built. No platform classes considered
  	(o excludeFromBuild) & (configuration isAbstractBaseClass not)         This is a concrete [Lang][VM][MemoryManager][etc] configuration that will be NOT built.
  	(o excludeFromBuild not) | (configuration isAbstractBaseClass)          concrete implementation may depend on its [OS][VMWordSize][Processor] AbstractBaseClass for platform level methods. 
  																		   example: Linux32x86Config ccBuild has the '-m32' compiler flag that is common to all builds on that platform
  	(o excludeFromBuild not) & (configuration isAbstractBaseClass)       Not allowed. [OS][VMWordSize][Processor] AbstractBaseClasses should not be built. This is a useful test in its own right.
  	(o excludeFromBuild) & (configuration isAbstractBaseClass)             These are the AbstractBaseClasses. An AbstractBaseClass should always be excluded from a build
  
  
  HelpBrowser openOn: CMakeVMMakerSqueakDeveloperHelp
  tty.!
  CPlatformConfigForSqueak class
  	instanceVariableNames: 'isAbstractBaseClass'!

Item was changed:
  ----- Method: CPlatformConfigForSqueak>>compilerFlags (in category 'compiling') -----
  compilerFlags
- 	self flag:'tty'. "This goes away if we agree to fork the  project. "
  	self deprecated:' this catchall method has been split into dedicated methods: cmakePrefixPath cmakeIncludePath 	cmakeLibraryPath	cmakeIncludeModules;    cmakeCFlags;       '. "see method ''generate'' in CMakeVMGeneratorForSqueak browse      for old call.  "
  	self	 cmakeCFlags.
  
  
  "The old CMakeVMMaker loaded all kinds of stuff in compilerflags that where really pre-processor definitions etc. 
  I have factored them out in the interest of clarity and simplicity.
  "!

Item was added:
+ ----- Method: CPlatformConfigForSqueak>>defaultExternalPlugins (in category 'plugins') -----
+ defaultExternalPlugins
+ 	self shouldBeImplemented !

Item was added:
+ ----- Method: CPlatformConfigForSqueak>>defaultInternalPlugins (in category 'plugins') -----
+ defaultInternalPlugins
+ 	self shouldBeImplemented !

Item was added:
+ ----- Method: CPlatformConfigForSqueak>>dirPlatforms (in category 'cmake directory') -----
+ dirPlatforms
+ 	^'platforms'!

Item was added:
+ ----- Method: CPlatformConfigForSqueak>>doesNotUnderstand: (in category 'utils') -----
+ doesNotUnderstand: aMessage
+ 	" ignore configureXYZ: messages "
+ 
+ 	| sel  |
+ 	sel := aMessage selector.
+ 	
+ 	((sel beginsWith: 'configure') and: [
+ 		(sel indexOf: $: ) = sel size ] ) ifTrue: [ ^ self ].
+ 	
+ 	^ super doesNotUnderstand: aMessage!

Item was added:
+ ----- Method: CPlatformConfigForSqueak>>isLittleEndian (in category 'testing') -----
+ isLittleEndian
+ 	"default is true. Override if necessary"
+ 	^ true!

Item was added:
+ ----- Method: CPlatformConfigForSqueak>>platformName (in category 'accessing') -----
+ platformName
+ 	"override in subclass"
+ 	self subclassResponsibility !

Item was removed:
- ----- Method: CPlatformConfigForSqueak>>prepareForGeneration (in category 'source generation') -----
- prepareForGeneration
- 	"feel free to override me"
- 	|i|
- 	self flag:'tty'. 
- 	i:= self interpreterClass.
- 	((i == CoInterpreter) | (i == CoInterpreterMT ))
- 		ifTrue:[self prepareForCogGeneration].   "what is more efficient? self or super?  tty."
- 	(i == StackInterpreter) 
- 		ifTrue:[self prepareForStackVMGeneration].
- 
- !

Item was changed:
  ----- Method: CPlatformConfigForSqueak>>prepareVMMaker (in category 'squeak compatability') -----
  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 dirPlatforms.
- 	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 removed:
- ----- Method: CPlatformConfigForSqueak>>thirdpartyLibs (in category 'cmake buildType redirects') -----
- thirdpartyLibs
- 	"Route this message send to the message appropriate for my buildType "
- 	|d |
- 	d:= SqueakCMakeVMMakerAbstractBuilder default buildTypeAndDirectoryInfo copy.
- 	d 
- 		at: #build put: [self thirdpartyLibsBuild];
- 		at: #buildAssert  put: [self thirdpartyLibsBuildAssert];
- 		at: #buildAssertITimerHeartbeat  put: [self thirdpartyLibsBuildAssertITimerHeartbeat];
-             at:#buildDebug  put: [self thirdpartyLibsBuildDebug];   
- 		at: #buildDebugITimerHeartbeat  put: [self thirdpartyLibsBuildDebugITimerHeartbeat ];
- 		at: #buildITimerHeartbeat  put: [self thirdpartyLibsBuildITimerHeartbeat];
- 		at: #buildMultiThreaded  put: [self thirdpartyLibsBuildMultiThreaded];
- 		at: #buildMultiThreadedAssert  put: [self thirdpartyLibsBuildMultiThreadedAssert];
- 		at: #buildMultiThreadedDebug   put: [self thirdpartyLibsBuildMultiThreadedDebug ];
- 		at: #buildNone put:[self thirdpartyLibsBuildNone].
- 	^(d at: buildType) value
- !

Item was removed:
- ----- Method: CPlatformConfigForSqueak>>thirdpartyLibsBuild (in category 'cmake buildType redirects') -----
- thirdpartyLibsBuild 
- 	"convenience method to customize third party libs for this buildType.  
- 
- 	SystemNavigation default browseMethodsWhoseNamesContain: 'addThirdpartyLibrary:'
- 
- 	SystemNavigation default browseMethodsWhoseNamesContain: 'processThirdpartyLibraries'	
- 
- 	SystemNavigation default browseMethodsWhoseNamesContain: 'thirdpartyLibs'
- 
- 	do nothing is an option
- 	"
- 	self subclassResponsibility
- !

Item was removed:
- ----- Method: CPlatformConfigForSqueak>>thirdpartyLibsBuildAssert (in category 'cmake buildType redirects') -----
- thirdpartyLibsBuildAssert 
- 	"convenience method to customize third party libs for this buildType.  
- 
- 	SystemNavigation default browseMethodsWhoseNamesContain: 'addThirdpartyLibrary:'
- 
- 	SystemNavigation default browseMethodsWhoseNamesContain: 'processThirdpartyLibraries'	
- 
- 	SystemNavigation default browseMethodsWhoseNamesContain: 'thirdpartyLibs'
- "
- 	^ self thirdpartyLibsBuild
- !

Item was removed:
- ----- Method: CPlatformConfigForSqueak>>thirdpartyLibsBuildAssertITimerHeartbeat (in category 'cmake buildType redirects') -----
- thirdpartyLibsBuildAssertITimerHeartbeat 
- 	"convenience method to customize third party libs for this buildType.  
- 
- 	SystemNavigation default browseMethodsWhoseNamesContain: 'addThirdpartyLibrary:'
- 
- 	SystemNavigation default browseMethodsWhoseNamesContain: 'processThirdpartyLibraries'	
- 
- 	SystemNavigation default browseMethodsWhoseNamesContain: 'thirdpartyLibs'
- "
- 	^ self thirdpartyLibsBuild!

Item was removed:
- ----- Method: CPlatformConfigForSqueak>>thirdpartyLibsBuildDebug (in category 'cmake buildType redirects') -----
- thirdpartyLibsBuildDebug 
- 	"convenience method to customize third party libs for this buildType.  
- 
- 	SystemNavigation default browseMethodsWhoseNamesContain: 'addThirdpartyLibrary:'
- 
- 	SystemNavigation default browseMethodsWhoseNamesContain: 'processThirdpartyLibraries'	
- 
- 	SystemNavigation default browseMethodsWhoseNamesContain: 'thirdpartyLibs'
- "
- 	^ self thirdpartyLibsBuild!

Item was removed:
- ----- Method: CPlatformConfigForSqueak>>thirdpartyLibsBuildDebugITimerHeartbeat (in category 'cmake buildType redirects') -----
- thirdpartyLibsBuildDebugITimerHeartbeat 
- 	"convenience method to customize third party libs for this buildType.  
- 
- 	SystemNavigation default browseMethodsWhoseNamesContain: 'addThirdpartyLibrary:'
- 
- 	SystemNavigation default browseMethodsWhoseNamesContain: 'processThirdpartyLibraries'	
- 
- 	SystemNavigation default browseMethodsWhoseNamesContain: 'thirdpartyLibs'
- "
- 	^ self thirdpartyLibsBuild
- !

Item was removed:
- ----- Method: CPlatformConfigForSqueak>>thirdpartyLibsBuildITimerHeartbeat (in category 'cmake buildType redirects') -----
- thirdpartyLibsBuildITimerHeartbeat 
- 	"convenience method to customize third party libs for this buildType.  
- 
- 	SystemNavigation default browseMethodsWhoseNamesContain: 'addThirdpartyLibrary:'
- 
- 	SystemNavigation default browseMethodsWhoseNamesContain: 'processThirdpartyLibraries'	
- 
- 	SystemNavigation default browseMethodsWhoseNamesContain: 'thirdpartyLibs'
- "
- 	^ self thirdpartyLibsBuild
- !

Item was removed:
- ----- Method: CPlatformConfigForSqueak>>thirdpartyLibsBuildMultiThreaded (in category 'cmake buildType redirects') -----
- thirdpartyLibsBuildMultiThreaded 
- 	"convenience method to customize third party libs for this buildType.  
- 
- 	SystemNavigation default browseMethodsWhoseNamesContain: 'addThirdpartyLibrary:'
- 
- 	SystemNavigation default browseMethodsWhoseNamesContain: 'processThirdpartyLibraries'	
- 
- 	SystemNavigation default browseMethodsWhoseNamesContain: 'thirdpartyLibs'
- "
- 	^ self thirdpartyLibsBuild!

Item was removed:
- ----- Method: CPlatformConfigForSqueak>>thirdpartyLibsBuildMultiThreadedAssert (in category 'cmake buildType redirects') -----
- thirdpartyLibsBuildMultiThreadedAssert
- 	"convenience method to customize third party libs for this buildType.  
- 
- 	SystemNavigation default browseMethodsWhoseNamesContain: 'addThirdpartyLibrary:'
- 
- 	SystemNavigation default browseMethodsWhoseNamesContain: 'processThirdpartyLibraries'	
- 
- 	SystemNavigation default browseMethodsWhoseNamesContain: 'thirdpartyLibs'
- "
- 	^ self thirdpartyLibsBuild
- !

Item was removed:
- ----- Method: CPlatformConfigForSqueak>>thirdpartyLibsBuildMultiThreadedDebug (in category 'cmake buildType redirects') -----
- thirdpartyLibsBuildMultiThreadedDebug 
- 	"convenience method to customize third party libs for this buildType.  
- 
- 	SystemNavigation default browseMethodsWhoseNamesContain: 'addThirdpartyLibrary:'
- 
- 	SystemNavigation default browseMethodsWhoseNamesContain: 'processThirdpartyLibraries'	
- 
- 	SystemNavigation default browseMethodsWhoseNamesContain: 'thirdpartyLibs'
- "
- 	^ self thirdpartyLibsBuild!

Item was removed:
- ----- Method: CPlatformConfigForSqueak>>thirdpartyLibsBuildNoBuildType (in category 'cmake buildType redirects') -----
- thirdpartyLibsBuildNoBuildType
- 	"SHOULD NOT GET HERE"
- 	self shouldNotImplement.
- !

Item was removed:
- ----- Method: CPlatformConfigForSqueak>>x (in category 'cmake buildType redirects') -----
- x
- 	"Route this message send to the message appropriate for my buildType "
- 	|d |
- 	d:= SqueakCMakeVMMakerAbstractBuilder default buildTypeAndDirectoryInfo copy.
- 	d 
- 		at: #build put: [self xBuild];
- 		at: #buildAssert  put: [self xBuildAssert];
- 		at: #buildAssertITimerHeartbeat  put: [self xBuildAssertITimerHeartbeat];
-             at:#buildDebug  put: [self xBuildDebug];   
- 		at: #buildDebugITimerHeartbeat  put: [self xBuildDebugITimerHeartbeat ];
- 		at: #buildITimerHeartbeat  put: [self xBuildITimerHeartbeat];
- 		at: #buildMultiThreaded  put: [self xBuildMultiThreaded];
- 		at: #buildMultiThreadedAssert  put: [self xBuildMultiThreadedAssert];
- 		at: #buildMultiThreadedDebug   put: [self xBuildMultiThreadedDebug ];
- 		at: #buildNone put:[self xNoBuildType].
- 	^(d at: buildType) value!

Item was added:
+ ----- Method: InterpreterPlugin class>>generateFor:internal: (in category '*CMakeVMMakerSqueak') -----
+ generateFor: aCMakeVMGenerator internal: aBoolean 
+ 
+ 	^ aCMakeVMGenerator 
+ 		generatePlugin: self 
+ 		internal: aBoolean
+ 		extraRules: nil!

Item was removed:
- SqueakCMThirdpartyLibrary subclass: #SqueakCMFreetype2
- 	instanceVariableNames: ''
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'CMakeVMMakerSqueak-Libs'!
- 
- !SqueakCMFreetype2 commentStamp: '<historical>' prior: 0!
- This is a configuration for building freetype2 library!

Item was removed:
- ----- Method: SqueakCMFreetype2 class>>canonicalName (in category 'accessing') -----
- canonicalName
- 	^ 'freetype2'!

Item was removed:
- ----- Method: SqueakCMFreetype2>>archiveMD5Sum (in category 'package properties') -----
- archiveMD5Sum
- 
- 	^ 'c15f6dc8ed190d67b89ae09aaf7896b4'!

Item was removed:
- ----- Method: SqueakCMFreetype2>>build (in category 'generating actions') -----
- build
- 
- 	gen 
- 		puts:
- '
- add_custom_command(OUTPUT "${ft2config}"
- 	COMMAND ./configure --prefix=''${installPrefix}'' ', self configurationFlags, '
- 	WORKING_DIRECTORY "${libSourcesDir}"
- 	DEPENDS "${unpackTarget}"
- )
- add_custom_command(OUTPUT "${ft2libInstalled}"
- 	COMMAND make
- 	COMMAND make install
- 	WORKING_DIRECTORY "${libSourcesDir}"
- 	DEPENDS "${ft2config}"
- 	COMMENT "Building ${libName}"
- )
- '
- !

Item was removed:
- ----- Method: SqueakCMFreetype2>>copyArtefacts (in category 'generating actions') -----
- copyArtefacts
- 
- 	self 
- 		copy: '${ft2libInstalled}' 
- 		to: '${externalModulesDir}/${libraryFileName}'.!

Item was removed:
- ----- Method: SqueakCMFreetype2>>defineAsTarget (in category 'generating actions') -----
- defineAsTarget
- 
- 	gen puts:
- 	
- '
- add_custom_target(${libName} 
- 	DEPENDS ${externalModulesDir}/${libraryFileName}
- 	)
- '
- 
- !

Item was removed:
- ----- Method: SqueakCMFreetype2>>defineGlobalTargets (in category 'generating actions') -----
- defineGlobalTargets
- 	| var |
- 	var := self canonicalName , '_LIB'.
- 	vmGen set: var toString: self targetForLinking.
- "
- define a library as imported one
- and make it depend from it's build target
- "
- 	vmGen
- 		puts: 
- ('add_library("{1}" SHARED IMPORTED GLOBAL)
- 	set_target_properties("{1}" PROPERTIES IMPORTED_LOCATION "{1}")
- add_dependencies("{1}" "{2}")
- ' format: { '${',var, '}' . self buildTarget }
- ).
- 
- 	vmGen cmd: 'add_dependencies' params:
- 		vmGen moduleName , ' ' , self buildTarget!

Item was removed:
- ----- Method: SqueakCMFreetype2>>downloadURL (in category 'package properties') -----
- downloadURL
- 	^ 'http://ftp.igh.cnrs.fr/pub/nongnu/freetype/freetype-2.4.9.tar.gz'
- !

Item was removed:
- ----- Method: SqueakCMFreetype2>>includeDir (in category 'accessing') -----
- includeDir
- 	"see setVariables"
- 
- " `<prefix>/include/freetype2' must be in your current inclusion path "
- 
- 
- 	^ '"${thirdpartyDir}/out/include" "${thirdpartyDir}/out/include/freetype2"'!

Item was removed:
- ----- Method: SqueakCMFreetype2>>libraryFileName (in category 'package properties') -----
- libraryFileName
- 	^ 'libfreetype.6.dylib'!

Item was removed:
- ----- Method: SqueakCMFreetype2>>setVariables (in category 'generating actions') -----
- setVariables
- 	super setVariables.
- 	
- "add include path"
- 	gen 
- 		set: #freetype2_includeDir toString: '${installPrefix}/include';
- 		set: #libraryFileName to: self libraryFileName;
- 		set: #freetype2_location toString: '${externalModulesDir}/${libraryFileName}';
- 		set: #ft2config toString: '${libSourcesDir}/builds/unix/config.status';
- 	 	set: #ft2libInstalled toString: '${installPrefix}/lib/${libraryFileName}'!

Item was removed:
- ----- Method: SqueakCMFreetype2>>unpackedDirName (in category 'package properties') -----
- unpackedDirName
- 
- 	^ 'freetype-2.4.9'!

Item was removed:
- SqueakCMThirdpartyLibrary subclass: #SqueakCMOpenSSL
- 	instanceVariableNames: ''
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'CMakeVMMakerSqueak-Libs'!

Item was removed:
- ----- Method: SqueakCMOpenSSL class>>canonicalName (in category 'as yet unclassified') -----
- canonicalName
- 	^ 'openssl'!

Item was removed:
- CMThirdpartyLibrary subclass: #SqueakCMThirdpartyLibrary
- 	instanceVariableNames: ''
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'CMakeVMMakerSqueak-Libs'!
- 
- !SqueakCMThirdpartyLibrary commentStamp: 'tty 12/8/2014 11:25' prior: 0!
- N.B. tty: I have not parsed these in depth as of 2014.12.09
- 
- A SqueakCMThirdpartyLibrary is the root library for copies of classes in CMakeVMMaker-Libs.  
- I replace only the Squeak incompatible methods of my parent
- 
- !

Item was removed:
- ----- Method: SqueakCMThirdpartyLibrary class>>canonicalName (in category 'as yet unclassified') -----
- canonicalName
- 	"answer the library canonical name, like 
- 		'freetype2'
- 		or 'cairo' 
- 		etc.
- 		
- 	Note , this method is used to find the corresponding library
- 	from all subclasses of CMThirdpartyLibrary	
- 	"
- 	^ self subclassResponsibility!

Item was removed:
- ----- Method: SqueakCMThirdpartyLibrary class>>named:config: (in category 'as yet unclassified') -----
- named: aName config: aCPlatformConfig
- 
- 	^ (self allSubclasses detect: [:cls | 
- 		cls canonicalName = aName and: [ cls supports: aCPlatformConfig ] ])
- 		new!

Item was removed:
- ----- Method: SqueakCMThirdpartyLibrary class>>platformName (in category 'as yet unclassified') -----
- platformName 
- 	^nil!

Item was removed:
- ----- Method: SqueakCMThirdpartyLibrary class>>supports: (in category 'as yet unclassified') -----
- supports: aConfig
- 	"default implementation"
- 	^ self platformName = aConfig platformName !

Item was removed:
- ----- Method: SqueakCMThirdpartyLibrary>>generateFor: (in category 'as yet unclassified') -----
- generateFor: aVMGenerator
- 
- 	| libDir stream contents |
- 	self flag:'tty'. "This l must be transformed to generateByTemplateFor: and the output converted to CMakeTemplates"
- 	self break.
- 	vmGen := aVMGenerator.
- 	
- 	gen := CMakeGeneratorForSqueak new
- 		output: (String new writeStream).
- 	
- 	libDir := (aVMGenerator thirdpartyDir / self canonicalName) assureExistence.
- 
- 	stream := String new writeStream.
- 	
- 	self generate.
- 
- 	stream nextPutAll: (vmGen config fixLineEndsOf: gen output contents).
- 
- 	contents := stream contents. 
- 	
- 	(self isFile: (libDir  / gen outputFileName) fullName hasContents: contents) ifFalse: [
- 		"contents changed, update the file. Because fucking cmake will force rebuild everything if we change its modification date
- 		without changing its contents"
- 		(FileStream forceNewFileNamed: (libDir  / gen outputFileName) pathName) nextPutAll: contents; close.
- 		].
- 	
- 
- 	vmGen addSubdirectory:  vmGen thirdpartyDirName , '/' , self canonicalName.
- 	self defineGlobalTargets.
- 	!

Item was removed:
- SqueakCMFreetype2 subclass: #SqueakCMWin32Freetype2
- 	instanceVariableNames: ''
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'CMakeVMMakerSqueak-Libs'!
- 
- !SqueakCMWin32Freetype2 commentStamp: '<historical>' prior: 0!
- Some overrides to make freetype build on windows:
- 
- Two artifacts to copy:
- 
- libfreetype.dll.a
- libfreetype-6.dll
- 
- the first one is used at link time with FTPlugin to 
- designate the exported symbols of .dll as well as .dll file name.
- 
- The second one is ready to use library produced by freetype makefiles.
- 
- We pass
- 
-  -march=i686
- 
- instead of
- 
-  -arch i386
- 
- to freetype configure, because MSYS GCC on windows don't understands the -arch option.
- !

Item was removed:
- ----- Method: SqueakCMWin32Freetype2 class>>platformName (in category 'as yet unclassified') -----
- platformName 
- 	^'win32'!

Item was removed:
- ----- Method: SqueakCMWin32Freetype2>>copyArtefacts (in category 'generating actions') -----
- copyArtefacts
- 
- 	gen puts:
- 'add_custom_command(
- 	OUTPUT "${externalModulesDir}/${libraryFileName}"
- 	COMMAND cp "${ft2libInstalled}" "${externalModulesDir}"
- 	COMMAND cp "${ft2binInstalled}" "${externalModulesDir}"
- 	DEPENDS "${ft2libInstalled}"
- )'!

Item was removed:
- ----- Method: SqueakCMWin32Freetype2>>defaultConfigurationFlags (in category 'settings') -----
- defaultConfigurationFlags 
- 	^#(
- 		'CFLAGS=''-march=i686''' 
- 		'LDFLAGS=''-march=i686''')!

Item was removed:
- ----- Method: SqueakCMWin32Freetype2>>defineGlobalTargets (in category 'generating actions') -----
- defineGlobalTargets
- 	| var |
- 	var := self canonicalName , '_LIB'.
- 	vmGen set: var toString: self targetForLinking.
- "
- define a library as imported one
- and make it depend from it's build target
- "
- 	vmGen
- 		puts: 
- ('add_library("{1}" STATIC IMPORTED GLOBAL)
- 	set_target_properties("{1}" PROPERTIES IMPORTED_LOCATION "{1}")
- add_dependencies("{1}" "{2}")
- ' format: { '${',var, '}' . self buildTarget }
- ).
- 
- 	vmGen cmd: 'add_dependencies' params:
- 		vmGen moduleName , ' ' , self buildTarget!

Item was removed:
- ----- Method: SqueakCMWin32Freetype2>>libraryFileName (in category 'package properties') -----
- libraryFileName
- 	^ 'libfreetype.dll.a'!

Item was removed:
- ----- Method: SqueakCMWin32Freetype2>>setVariables (in category 'generating actions') -----
- setVariables
- 	super setVariables.
- 	
- "add include path"
- 	gen 
- 		set: #freetype2_includeDir toString: '${installPrefix}/include';
- 		set: #libraryFileName to: self libraryFileName;
- 		set: #freetype2_location toString: '${externalModulesDir}/${libraryFileName}';
- 		set: #ft2config toString: '${libSourcesDir}/builds/unix/config.status';
- 	 	set: #ft2libInstalled toString: '${installPrefix}/lib/${libraryFileName}';
- 	 	set: #ft2binInstalled toString: '${installPrefix}/bin/libfreetype-6.dll'.
- 		!

Item was removed:
- SqueakCMOpenSSL subclass: #SqueakCMWin32OpenSSL
- 	instanceVariableNames: ''
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'CMakeVMMakerSqueak-Libs'!

Item was removed:
- ----- Method: SqueakCMWin32OpenSSL class>>platformName (in category 'as yet unclassified') -----
- platformName 
- 	^'win32'!

Item was removed:
- ----- Method: SqueakCMWin32OpenSSL>>archiveMD5Sum (in category 'as yet unclassified') -----
- archiveMD5Sum
- 	"answer the MD5 checksum (in string) for downloaded library archive 
- 	(to check that downloaded file is not corrupt).
- 	
- 	You can take this sum by issuing:
- 	  md5 filename
- 	from command line
- 	"
- 	^ 'ae412727c8c15b67880aef7bd2999b2e'!

Item was removed:
- ----- Method: SqueakCMWin32OpenSSL>>build (in category 'as yet unclassified') -----
- build
- 
- 	gen 
- 		puts:
- '
- add_custom_command(OUTPUT "${libSourcesDir}/Makefile"
- 	COMMAND ./config shared --prefix=''${installPrefix}'' 
- 	WORKING_DIRECTORY "${libSourcesDir}"
- 	DEPENDS "${unpackTarget}"
- )
- 
- add_custom_command(OUTPUT "${installPrefix}/bin/libeay32.dll" "${installPrefix}/bin/ssleay32.dll"
- 	COMMAND make
- 	COMMAND make install
- 	WORKING_DIRECTORY "${libSourcesDir}"
- 	DEPENDS "${libSourcesDir}/Makefile"
- 	COMMENT "Building ${libName}"
- )
- '
- !

Item was removed:
- ----- Method: SqueakCMWin32OpenSSL>>configurationFlags (in category 'as yet unclassified') -----
- configurationFlags
- 	^ 'shared'!

Item was removed:
- ----- Method: SqueakCMWin32OpenSSL>>copyArtefacts (in category 'as yet unclassified') -----
- copyArtefacts 
- 
- 	self copy: '${installPrefix}/bin/libeay32.dll' to: '${externalModulesDir}/libeay32.dll'.
- 	self copy: '${installPrefix}/bin/ssleay32.dll' to: '${externalModulesDir}/ssleay32.dll'.
- "	self copy: '${installPrefix}/lib/libssl.dll.a' to: '${externalModulesDir}/libssl.dll.a'.
- 	self copy: '${installPrefix}/lib/libcrypto.dll.a' to: '${externalModulesDir}/libcrypto.dll.a'.
- "
- "
- 'libcrypto.dll.a' 'libssl.dll.a'.
- "!

Item was removed:
- ----- Method: SqueakCMWin32OpenSSL>>defineAsTarget (in category 'as yet unclassified') -----
- defineAsTarget 
- 	
- 	gen puts:
- 	'add_custom_target(', self buildTarget , '
- 		DEPENDS 
- 		"${externalModulesDir}/libeay32.dll"
- 		"${externalModulesDir}/ssleay32.dll"
- 	)'
- 	
- 		"${externalModulesDir}/${libraryFileName}"
- !

Item was removed:
- ----- Method: SqueakCMWin32OpenSSL>>defineGlobalTargets (in category 'as yet unclassified') -----
- defineGlobalTargets 
- 
- !

Item was removed:
- ----- Method: SqueakCMWin32OpenSSL>>downloadURL (in category 'as yet unclassified') -----
- downloadURL 
- 	^'http://www.openssl.org/source/openssl-1.0.1c.tar.gz'!

Item was removed:
- ----- Method: SqueakCMWin32OpenSSL>>includeDir (in category 'as yet unclassified') -----
- includeDir
- 
- 	^ '"${thirdpartyDir}/out/include"'!

Item was removed:
- ----- Method: SqueakCMWin32OpenSSL>>libraryFileName (in category 'as yet unclassified') -----
- libraryFileName
- 	^ 'libssl.dll.a'!

Item was removed:
- ----- Method: SqueakCMWin32OpenSSL>>setVariables (in category 'as yet unclassified') -----
- setVariables 
- 	super setVariables.
- 	
- 	gen
- 		set: #libraryFileName to: self libraryFileName;
- 		set: #libInstalled to: '${installPrefix}/lib/${libraryFileName}'!

Item was removed:
- ----- Method: SqueakCMWin32OpenSSL>>unpackedDirName (in category 'as yet unclassified') -----
- unpackedDirName
- 	^ 'openssl-1.0.1c'!

Item was changed:
  ----- Method: SqueakCMakeVMMakerAbstractBuilder>>enableMessageTracking: (in category 'building') -----
  enableMessageTracking: aBoolean
+ 	(config isKindOf: CPlatformConfigForSqueak)
- 	(config isKindOf: CPlatformConfig)
  		ifTrue:[config enabledebugmessages: aBoolean]
  		!

Item was changed:
  ----- Method: SqueakCMakeVMMakerAbstractBuilder>>generateSources (in category 'building') -----
  generateSources
+ 	(config isKindOf: CPlatformConfigForSqueak)
- 	self flag: 'tty'. "This used to work, but it looks like CPlaformConfig>>generateSources breaks at 'maker cogitClass: cg'"
- 	self error:'Pharo CPlatformConfig is broken. Will fix later'.
- 	(config isKindOf: CPlatformConfig)
  		ifTrue:[config generateSources]
  		!

Item was changed:
  ----- Method: SqueakMacintoshConfig>>cmakeWriteDirectoriesDotCmake: (in category 'cmake') -----
  cmakeWriteDirectoriesDotCmake: aMaker
  	|temp o|
  	"We could put these inline, but other components include the directories.cmake file. So, we continue that convention"
  	o := String new writeStream.
  	temp := OrderedCollection new.
  	temp
  		addLast: ((CMakeSet new) variable: 'topDir' quotedValue: (self topDir fullName));
  		addLast: ((CMakeSet new) variable: 'buildDir' quotedValue: (self buildDir ifNil: ['${topDir}/build'] ifNotNil: [self buildDir fullName]));
  		addLast: ((CMakeSet new) variable: 'thirdpartyDir' quotedValue: '${buildDir}/thirdParty');
+ 		addLast: ((CMakeSet new) variable: 'platformsDir' quotedValue: (self dirPlatforms));
- 		addLast: ((CMakeSet new) variable: 'platformsDir' quotedValue: (self platformsDir));
  		addLast: ((CMakeSet new) variable: 'srcDir' quotedValue: (self dirSource pathName));    "where the vm source directory lives"
  		addLast: ((CMakeSet new) variable: 'cogDir' quotedValue: (self cogDir pathName));        "oscogvm/src  for historical reasons" 
  		addLast: ((CMakeSet new) variable: 'srcPluginsDir' quotedValue: (pluginsDir ifNil: [ '${cogDir}/plugins' ]));  "plugin source directory only in oscogvm/src/plugins"
  		addLast: ((CMakeSet new) variable: 'srcVMDir' quotedValue: '${srcDir}/vm');
  		addLast: ((CMakeSet new) variable: 'platformName' quotedValue: (self platformName));
  		addLast: ((CMakeSet new) variable: 'targetPlatform' quotedValue: '${platformsDir}/${platformName}');
  		addLast: ((CMakeSet new) variable: 'crossDir' quotedValue: '${platformsDir}/Cross');
  		addLast: ((CMakeSet new) variable: 'platformVMDir' quotedValue: '${targetPlatform}/vm}');
  		addLast: ((CMakeSet new) variable: 'outputDir' quotedValue: (self outputDir fullName));
  		addLast: ((CMakeSet new) variable: 'externalModulesDir' quotedValue: (self externalModulesDir)).
  	temp do: [:each |  o nextPutAll: (each content); cr].
  	self write: (o contents) toFile: 'directories.cmake'.
  	(enabledebugmessages)
  		ifTrue:[	
  	templates 
  		addLast:((CMakeMessage new) message: (self class name), ' setDirectories: aMaker' )
  	].
  	templates addLast: ((CMakeInclude new) file: 'directories.cmake').
  
  !

Item was removed:
- ----- Method: SqueakMacintoshConfig>>defaultDirectoriesFromGitDir: (in category 'accessing') -----
- defaultDirectoriesFromGitDir: gitRepository
- 	"Set the default values for all necessary directories taking into account the Git repostiory. An example to use this method is:
- 	MTCocoaIOSCogJitDebugConfig new
- 	defaultDirectoriesFromGitDir: '/Users/mariano/Pharo/vm/git/cogVM/blessed';
- 	generateSources; 
- 	generate.
- 	"
- 	| gitRepositoryString |
- 	self flag:'tty'. "Squeak don't git"
- 	gitRepositoryString :=  gitRepository, '/'.
- 	self srcDir: gitRepositoryString, self srcDirName.
-     	self platformsDir: gitRepositoryString, self platformsDirName.
-     	self buildDir: gitRepositoryString, self buildDirName.
- 	self resourcesDir: gitRepositoryString, self resourcesDirName.
- 	self outputDir: gitRepositoryString, self outputDirName.
- 	
- 	
- 	!

Item was removed:
- ----- Method: SqueakMacintoshConfig>>thirdpartyLibsBuild (in category 'cmake buildType redirects') -----
- thirdpartyLibsBuild
- 	^ thirdpartyLibs ifNil: [ thirdpartyLibs := OrderedCollection new ].!

Item was removed:
- ----- Method: SqueakMacintoshConfig>>thirdpartyLibsBuildAssert (in category 'cmake buildType redirects') -----
- thirdpartyLibsBuildAssert
- 	^ self thirdpartyLibs !

Item was removed:
- ----- Method: SqueakMacintoshConfig>>thirdpartyLibsBuildAssertITimerHeartbeat (in category 'cmake buildType redirects') -----
- thirdpartyLibsBuildAssertITimerHeartbeat
- 	^ self thirdpartyLibs !

Item was removed:
- ----- Method: SqueakMacintoshConfig>>thirdpartyLibsBuildDebug (in category 'cmake buildType redirects') -----
- thirdpartyLibsBuildDebug
- 	^ self thirdpartyLibs !

Item was removed:
- ----- Method: SqueakMacintoshConfig>>thirdpartyLibsBuildDebugITimerHeartbeat (in category 'cmake buildType redirects') -----
- thirdpartyLibsBuildDebugITimerHeartbeat
- 	^ self thirdpartyLibs !

Item was removed:
- ----- Method: SqueakMacintoshConfig>>thirdpartyLibsBuildITimerHeartbeat (in category 'cmake buildType redirects') -----
- thirdpartyLibsBuildITimerHeartbeat
- 	^ self thirdpartyLibs !

Item was removed:
- ----- Method: SqueakMacintoshConfig>>thirdpartyLibsBuildMultiThreaded (in category 'cmake buildType redirects') -----
- thirdpartyLibsBuildMultiThreaded
- 	^ self thirdpartyLibs !

Item was removed:
- ----- Method: SqueakMacintoshConfig>>thirdpartyLibsBuildMultiThreadedAssert (in category 'cmake buildType redirects') -----
- thirdpartyLibsBuildMultiThreadedAssert
- 	^ self thirdpartyLibs !

Item was removed:
- ----- Method: SqueakMacintoshConfig>>thirdpartyLibsBuildMultiThreadedDebug (in category 'cmake buildType redirects') -----
- thirdpartyLibsBuildMultiThreadedDebug
- 	^ self thirdpartyLibs !

Item was changed:
  ----- Method: SqueakUnixConfig>>cmakeWriteDirectoriesDotCmake: (in category 'cmake') -----
  cmakeWriteDirectoriesDotCmake: aMaker
  	|temp o|
  	"We could put these inline, but other components include the directories.cmake file. So, we continue that convention"
  	o := String new writeStream.
  	temp := OrderedCollection new.
  	temp
  		addLast: ((CMakeSet new) variable: 'topDir' quotedValue: (self topDir fullName));
  		addLast: ((CMakeSet new) variable: 'buildDir' quotedValue: (self buildDir ifNil: ['${topDir}/build'] ifNotNil: [self buildDir fullName]));
  		addLast: ((CMakeSet new) variable: 'thirdpartyDir' quotedValue: '${buildDir}/thirdParty');
+ 		addLast: ((CMakeSet new) variable: 'platformsDir' quotedValue: (self dirPlatforms));
- 		addLast: ((CMakeSet new) variable: 'platformsDir' quotedValue: (self platformsDir));
  		addLast: ((CMakeSet new) variable: 'srcDir' quotedValue: (self dirSource pathName));    "where the vm source directory lives"
  		addLast: ((CMakeSet new) variable: 'cogDir' quotedValue: (self cogDir pathName));        "oscogvm/src  for historical reasons" 
  		addLast: ((CMakeSet new) variable: 'srcPluginsDir' quotedValue: (pluginsDir ifNil: [ '${cogDir}/plugins' ]));  "plugin source directory only in oscogvm/src/plugins"
  		addLast: ((CMakeSet new) variable: 'srcVMDir' quotedValue: '${srcDir}/vm');
  		addLast: ((CMakeSet new) variable: 'platformName' quotedValue: (self platformName));
  		addLast: ((CMakeSet new) variable: 'targetPlatform' quotedValue: '${platformsDir}/${platformName}');
  		addLast: ((CMakeSet new) variable: 'crossDir' quotedValue: '${platformsDir}/Cross');
  		addLast: ((CMakeSet new) variable: 'platformVMDir' quotedValue: '${targetPlatform}/vm}');
  		addLast: ((CMakeSet new) variable: 'outputDir' quotedValue: (self outputDir fullName));
  		addLast: ((CMakeSet new) variable: 'externalModulesDir' quotedValue: (self externalModulesDir)).
  	temp do: [:each |  o nextPutAll: (each content); cr].
  	self write: (o contents) toFile: 'directories.cmake'.
  	(enabledebugmessages)
  		ifTrue:[	
  	templates 
  		addLast:((CMakeMessage new) message: (self class name), ' setDirectories: aMaker' )
  	].
  	templates addLast: ((CMakeInclude new) file: 'directories.cmake').
  
  !

Item was removed:
- ----- Method: SqueakUnixConfig>>thirdpartyLibsBuild (in category 'cmake buildType redirects') -----
- thirdpartyLibsBuild
- 	^ thirdpartyLibs ifNil: [ thirdpartyLibs := OrderedCollection new ].!

Item was changed:
  ----- Method: SqueakWindowsConfig>>cmakeWriteDirectoriesDotCmake: (in category 'cmake') -----
  cmakeWriteDirectoriesDotCmake: aMaker
  	|temp o|
  	"We could put these inline, but other components include the directories.cmake file. So, we continue that convention"
  	o := String new writeStream.
  	temp := OrderedCollection new.
  	temp
  		addLast: ((CMakeSet new) variable: 'topDir' quotedValue: (self topDir fullName));
  		addLast: ((CMakeSet new) variable: 'buildDir' quotedValue: (self buildDir ifNil: ['${topDir}/build'] ifNotNil: [self buildDir fullName]));
  		addLast: ((CMakeSet new) variable: 'thirdpartyDir' quotedValue: '${buildDir}/thirdParty');
+ 		addLast: ((CMakeSet new) variable: 'platformsDir' quotedValue: (self dirPlatforms));
- 		addLast: ((CMakeSet new) variable: 'platformsDir' quotedValue: (self platformsDir));
  		addLast: ((CMakeSet new) variable: 'srcDir' quotedValue: (self dirSource pathName));    "where the vm source directory lives"
  		addLast: ((CMakeSet new) variable: 'cogDir' quotedValue: (self cogDir pathName));        "oscogvm/src  for historical reasons" 
  		addLast: ((CMakeSet new) variable: 'srcPluginsDir' quotedValue: (pluginsDir ifNil: [ '${cogDir}/plugins' ]));  "plugin source directory only in oscogvm/src/plugins"
  		addLast: ((CMakeSet new) variable: 'srcVMDir' quotedValue: '${srcDir}/vm');
  		addLast: ((CMakeSet new) variable: 'platformName' quotedValue: (self platformName));
  		addLast: ((CMakeSet new) variable: 'targetPlatform' quotedValue: '${platformsDir}/${platformName}');
  		addLast: ((CMakeSet new) variable: 'crossDir' quotedValue: '${platformsDir}/Cross');
  		addLast: ((CMakeSet new) variable: 'platformVMDir' quotedValue: '${targetPlatform}/vm}');
  		addLast: ((CMakeSet new) variable: 'outputDir' quotedValue: (self outputDir fullName));
  		addLast: ((CMakeSet new) variable: 'externalModulesDir' quotedValue: (self externalModulesDir)).
  	temp do: [:each |  o nextPutAll: (each content); cr].
  	self write: (o contents) toFile: 'directories.cmake'.
  	(enabledebugmessages)
  		ifTrue:[	
  	templates 
  		addLast:((CMakeMessage new) message: (self class name), ' setDirectories: aMaker' )
  	].
  	templates addLast: ((CMakeInclude new) file: 'directories.cmake').
  
  !

Item was removed:
- ----- Method: SqueakWindowsConfig>>thirdpartyLibsBuild (in category 'cmake buildType redirects') -----
- thirdpartyLibsBuild
- 	^ thirdpartyLibs ifNil: [ thirdpartyLibs := OrderedCollection new ].!

Item was removed:
- ----- Method: SqueakWindowsConfig>>thirdpartyLibsBuildAssert (in category 'cmake buildType redirects') -----
- thirdpartyLibsBuildAssert
- 	^ self thirdpartyLibs !

Item was removed:
- ----- Method: SqueakWindowsConfig>>thirdpartyLibsBuildAssertITimerHeartbeat (in category 'cmake buildType redirects') -----
- thirdpartyLibsBuildAssertITimerHeartbeat
- 	^ self thirdpartyLibs !

Item was removed:
- ----- Method: SqueakWindowsConfig>>thirdpartyLibsBuildDebug (in category 'cmake buildType redirects') -----
- thirdpartyLibsBuildDebug
- 	^ self thirdpartyLibs !

Item was removed:
- ----- Method: SqueakWindowsConfig>>thirdpartyLibsBuildDebugITimerHeartbeat (in category 'cmake buildType redirects') -----
- thirdpartyLibsBuildDebugITimerHeartbeat
- 	^ self thirdpartyLibs !

Item was removed:
- ----- Method: SqueakWindowsConfig>>thirdpartyLibsBuildITimerHeartbeat (in category 'cmake buildType redirects') -----
- thirdpartyLibsBuildITimerHeartbeat
- 	^ self thirdpartyLibs !

Item was removed:
- ----- Method: SqueakWindowsConfig>>thirdpartyLibsBuildMultiThreaded (in category 'cmake buildType redirects') -----
- thirdpartyLibsBuildMultiThreaded
- 	^ self thirdpartyLibs !

Item was removed:
- ----- Method: SqueakWindowsConfig>>thirdpartyLibsBuildMultiThreadedAssert (in category 'cmake buildType redirects') -----
- thirdpartyLibsBuildMultiThreadedAssert
- 	^ self thirdpartyLibs !

Item was removed:
- ----- Method: SqueakWindowsConfig>>thirdpartyLibsBuildMultiThreadedDebug (in category 'cmake buildType redirects') -----
- thirdpartyLibsBuildMultiThreadedDebug
- 	^ self thirdpartyLibs !



More information about the Vm-dev mailing list