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

commits at source.squeak.org commits at source.squeak.org
Wed Jun 18 20:54:12 UTC 2014


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

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

Name: CMakeVMMakerSqueak-tty.66
Author: tty
Time: 18 June 2014, 3:44:39.014 pm
UUID: 69e9e4e4-1b11-4493-9f0d-6e51a73e76d0
Ancestors: CMakeVMMakerSqueak-tty.65

CPlatformConfigSqueak in place.

Started massive refactoring.

All current tests pass, so pushing this version at that milestone.

Next up: more refactoring

=============== Diff against CMakeVMMakerSqueak-tty.65 ===============

Item was added:
+ ----- Method: CMakeVMMakerSqueakConfigurationsTest>>testCogitClass (in category 'as yet unclassified') -----
+ testCogitClass
+ 	"for each builder that does not exclude itself from builds, make sure it returns cogitClass "
+ 	SqueakCMakeVMMakerAbstractBuilder 
+ 		subclassesDo:[:builder | | o |
+ 			Smalltalk globals 
+ 				allClassesDo:[:configuration | (configuration class category asString withoutQuoting startsWith: (builder configurationsCategory))
+ 					ifTrue:[ 
+ 							o:= configuration new.
+ 							o excludeFromBuild not                                                     
+ 							 	ifTrue:[self assert:(o  cogitClass inheritsFrom: Cogit)]]]]
+ 
+ 
+ 
+ 
+ 
+ 
+ 
+ !

Item was added:
+ ----- Method: CMakeVMMakerSqueakConfigurationsTest>>testInterpreterClass (in category 'as yet unclassified') -----
+ testInterpreterClass
+ 	"for each builder that does not exclude itself from builds, make sure it returns an InterpreterClass "
+ 	SqueakCMakeVMMakerAbstractBuilder 
+ 		subclassesDo:[:builder | | o |
+ 			Smalltalk globals 
+ 				allClassesDo:[:configuration | (configuration class category asString withoutQuoting startsWith: (builder configurationsCategory))
+ 					ifTrue:[ 
+ 							o:= configuration new.
+ 							o excludeFromBuild not                                                     
+ 							 	ifTrue:[
+ 										self assert:(o  interpreterClass inheritsFrom: InterpreterPrimitives).
+ 										self assert:(o  interpreterClassBuild inheritsFrom: InterpreterPrimitives).
+ 										self assert:(o  interpreterClassBuildAssert inheritsFrom: InterpreterPrimitives).
+ 										self assert:(o  interpreterClassBuildAssertITimerHeartbeat inheritsFrom: InterpreterPrimitives).
+ 										self assert:(o  interpreterClassBuildDebug inheritsFrom: InterpreterPrimitives).
+ 										self assert:(o  interpreterClassBuildDebugITImerHeartbeat inheritsFrom: InterpreterPrimitives).
+ 										self assert:(o  interpreterClassBuildITimerHeartbeat inheritsFrom: InterpreterPrimitives).
+ 										self assert:(o  interpreterClassBuildITimerMultiThreaded inheritsFrom: InterpreterPrimitives).
+ 										self assert:(o  interpreterClassBuildITimerMultiThreadedAssert inheritsFrom: InterpreterPrimitives).
+ 										self assert:(o  interpreterClassBuildITimerMultiThreadedDebug inheritsFrom: InterpreterPrimitives)]]]]
+ 
+ 
+ 
+ 
+ 
+ 
+ 
+ !

Item was changed:
  CPlatformConfig subclass: #CPlatformConfigForSqueak
+ 	instanceVariableNames: 'buildType generateBuild generateBuildAssert generateBuildAssertITimerHeartbeat generateBuildDebug generateBuildDebugITimerHeartbeat generateBuildDebugMultiThreaded generateBuildIHeartbeatTimer generateBuildMultiThreaded generateBuildMultiThreadedAssert generateBuildMultiThreadedDebug'
- 	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'CMakeVMMakerSqueak'!
  
  !CPlatformConfigForSqueak commentStamp: 'tty 6/17/2014 17:53' 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 used to be a TCPlatformConfigForSqueak, but if you attempt to load CMakeVMMakerSqueak-tty.63 you will note that massive Traits applied to over a hundred classes load very slowly via Monticello.
  
  tty.!

Item was added:
+ ----- Method: CPlatformConfigForSqueak>>addDriver:sources:generator:externalLibs: (in category 'squeak compatability') -----
+ addDriver: name sources: aSources generator: cmakeGen externalLibs: extLibs
+ 
+ 	| cfg srcs |
+ 	
+ 	srcs := aSources inject: '' into: [:res :each | res , ' "', each, '"' ].
+ 	cfg := cmakeGen
+ 		captureOutputDuring: [
+ 			cmakeGen printHeader;
+ 			project: name;
+ 			include: '../directories.cmake';
+ 		
+ 			message: 'Adding module: ', name;
+ 			
+ 			addDefinitions:  self compilerFlags;
+ 			addDefinitions: '-fPIC -DPIC';
+ 			set: #sources to: srcs;
+ 			cmd: 'add_library' params: name, ' SHARED ${sources}'; 
+ 			includeDirectories: '${crossDir}/plugins/FilePlugin';
+ 			includeDirectories: '${targetPlatform}/plugins/B3DAcceleratorPlugin';
+ 			includeDirectories: '${crossDir}/plugins/B3DAcceleratorPlugin';
+ 			set: 'LIBRARY_OUTPUT_PATH' toString: self outputDir fullName;
+ 			addExternalLibraries: extLibs;
+ 			cmd: 'target_link_libraries' params: name , ' ${LINKLIBS}';
+ 			cmd: 'set_target_properties' params: name , ' PROPERTIES PREFIX "" SUFFIX "" 
+ 			LINK_FLAGS -m32' 
+ 	].
+ 	
+ 	(self buildDir / name) assureExistence.
+ 	self write: cfg toFile: name , '/', cmakeGen outputFileName.
+ 	cmakeGen addSubdirectory:  name.
+ 	!

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

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

Item was added:
+ ----- Method: CPlatformConfigForSqueak>>buildScript (in category 'squeak compatability') -----
+ buildScript
+ 	"answer the build script for building everything"
+ 	
+ 
+ 	^ 
+ '#!!/usr/bin/env bash
+ 
+ cmake .
+ make
+ 
+ '!

Item was changed:
+ ----- Method: CPlatformConfigForSqueak>>buildType: (in category 'squeak compatability') -----
+ buildType: aSymbol
+ 	buildType:= aSymbol!
- ----- Method: CPlatformConfigForSqueak>>buildType: (in category 'cmake configuration') -----
- buildType: aSymbol	
- 	"force suclass to implement instance var accessor"
- 	self subclassResponsibility.!

Item was added:
+ ----- Method: CPlatformConfigForSqueak>>cogitClass (in category 'source generation') -----
+ cogitClass
+ 	self subclassResponsibility
+ 
+ 	"
+ 	^SimpleStackBasedCogit
+ 	^ StackToRegisterMappingCogit 
+ 	^SistaStackToRegisterMappingCogit
+ 
+ 	Which one?
+ 
+ 	ClassCommentVersionsBrowser browseCommentOf: Cogit 
+ 
+ 	"
+ !

Item was changed:
  ----- Method: CPlatformConfigForSqueak>>compilerFlags (in category 'compiler flags') -----
  compilerFlags
+ 	|d commonFlags flags|
+ 	d:= SqueakCMakeVMMakerAbstractBuilder default buildTypeAndDirectoryInfo copy.
+ 	d 
+ 		at: #build put: [self compilerFlagsBuild];
+ 		at: #buildAssert  put: [self compilerFlagsAssert];
+ 		at: #buildAssertITimerHeartbeat  put: [self compilerFlagsAssertITimerHeartbeat];
+             at:#buildDebug  put: [self compilerFlagsDebug];   "located in CMakeVMMaker CPlatformConfig"
+ 		at: #buildDebugITimerHeartbeat  put: [self compilerFlagsDebugITimerHeartbeat ];
+ 		at: #buildITimerHeartbeat  put: [self compilerFlagsIHeartbeatTimer];
+ 		at: #buildMultiThreaded  put: [self compilerFlagsMultiThreaded ];
+ 		at: #buildMultiThreadedAssert  put: [self compilerFlagsMultiThreadedAssert];
+ 		at: #buildMultiThreadedDebug   put: [self compilerFlagsMultiThreadedDebug ];
+ 		at: #buildNone put:[self compilerFlagsNoBuildType].
+ 
+     flags:= String streamContents: [ :stream |
+ 	 (((d at:  buildType) value)  collect: #withBlanksTrimmed as: Set)
+ 		asStringOn: stream 
+ 		delimiter:' '].
+ 
+     commonFlags:=String streamContents: [ :stream |
+ 		((self commonCompilerFlags) collect: #withBlanksTrimmed as: Set)
+ 			asStringOn: stream 
+ 			delimiter: ' ' ].
+ 	^ commonFlags, ' ' ,flags.!
- 	self subclassResponsibility!

Item was added:
+ ----- Method: CPlatformConfigForSqueak>>dirFrom: (in category 'squeak compatability') -----
+ dirFrom: aStringOrDir
+ 	^ aStringOrDir isString
+ 		ifTrue: [ FileDirectory forFileName: aStringOrDir  ]
+ 		ifFalse: [ aStringOrDir ]!

Item was changed:
  ----- Method: CPlatformConfigForSqueak>>executableName (in category 'accessing') -----
  executableName
  	self subclassResponsibility
+ "
+ executableName
+ 	^ self vmCogExecutableName
+ 	^ self vmSistaExecutableName
+ 	^ self vmStackExectuableName
+ "
+ !
- 
- "browse subclasses of CPLatformConfig for context
- ^'CogVM'
- ^ 'CogMTVM'
- ^ 'EventVM'.
- ^'iStackVMSimulator'
- ^ 'iStackVM'
- ^'Squeak'
- ^ 'StackVM'
- 
- 
- 
- "!

Item was added:
+ ----- Method: CPlatformConfigForSqueak>>externalModulesDir (in category 'accessing') -----
+ externalModulesDir
+ 	"answer the location in VM bundle, where plugins and rest of dynamic libs will be copied,
+ 	"
+ 	self subclassResponsibility!

Item was added:
+ ----- Method: CPlatformConfigForSqueak>>fixLineEndsOf: (in category 'squeak compatability') -----
+ fixLineEndsOf: string
+ 	^ string copyReplaceAll: String cr with: String crlf!

Item was changed:
  ----- Method: CPlatformConfigForSqueak>>frameworks (in category 'accessing') -----
  frameworks
+ 	self subclassResponsibility!
- 	"leave empty for all platforms but Mac OS"
- 	^ #()!

Item was changed:
+ ----- Method: CPlatformConfigForSqueak>>generate (in category 'squeak compatability') -----
- ----- Method: CPlatformConfigForSqueak>>generate (in category 'accessing') -----
  generate
  	self generatePluginsList. 
  	self generateLicense. 
  	^ CMakeVMGeneratorForSqueak generate: self !

Item was added:
+ ----- Method: CPlatformConfigForSqueak>>interpreterClass (in category 'source generation') -----
+ interpreterClass
+ 	"answer an interpreter class for VM source code generation"
+ 	self subclassResponsibility 
+ 
+ 
+ "
+ 	^ CoInterpreter
+ 	^ CoInterpreterMT
+ 	^ CoInterpreterMT
+ 	^ StackInterpreter
+ 	^ StackEvtAndroidInterpreter
+ 	??other
+ "!

Item was added:
+ ----- Method: CPlatformConfigForSqueak>>interpreterClassBuild (in category 'cmake config build type ') -----
+ interpreterClassBuild
+ 	"interpreter class can change to MultiThreaded for certain build types. For consistency sake, we maintain the pattern of other confiuration methods"
+ 	^self interpreterClass
+ 
+ 
+ !

Item was added:
+ ----- Method: CPlatformConfigForSqueak>>interpreterClassBuildAssert (in category 'cmake config build type ') -----
+ interpreterClassBuildAssert
+ 	"interpreter class can change to MultiThreaded for certain build types. For consistency sake, we maintain the pattern of other confiuration methods"
+ 	^self interpreterClass
+ 
+ 
+ !

Item was added:
+ ----- Method: CPlatformConfigForSqueak>>interpreterClassBuildAssertITimerHeartbeat (in category 'cmake config build type ') -----
+ interpreterClassBuildAssertITimerHeartbeat
+ 	"interpreter class can change to MultiThreaded for certain build types. For consistency sake, we maintain the pattern of other confiuration methods"
+ 	^self interpreterClass
+ 
+ 
+ !

Item was added:
+ ----- Method: CPlatformConfigForSqueak>>interpreterClassBuildDebug (in category 'cmake config build type ') -----
+ interpreterClassBuildDebug
+ 	"interpreter class can change to MultiThreaded for certain build types. For consistency sake, we maintain the pattern of other confiuration methods"
+ 	^self interpreterClass
+ 
+ 
+ !

Item was added:
+ ----- Method: CPlatformConfigForSqueak>>interpreterClassBuildDebugITImerHeartbeat (in category 'cmake config build type ') -----
+ interpreterClassBuildDebugITImerHeartbeat
+ 	"interpreter class can change to MultiThreaded for certain build types. For consistency sake, we maintain the pattern of other confiuration methods"
+ 	^self interpreterClass
+ 
+ 
+ !

Item was added:
+ ----- Method: CPlatformConfigForSqueak>>interpreterClassBuildITimerHeartbeat (in category 'cmake config build type ') -----
+ interpreterClassBuildITimerHeartbeat
+ 	"interpreter class can change to MultiThreaded for certain build types. For consistency sake, we maintain the pattern of other confiuration methods"
+ 	^self interpreterClass
+ 
+ 
+ !

Item was added:
+ ----- Method: CPlatformConfigForSqueak>>interpreterClassBuildITimerMultiThreaded (in category 'cmake config build type ') -----
+ interpreterClassBuildITimerMultiThreaded
+ 	"interpreter class can change to MultiThreaded for certain build types. For consistency sake, we maintain the pattern of other confiuration methods"
+ 	^CoInterpreterMT
+ 
+ 
+ !

Item was added:
+ ----- Method: CPlatformConfigForSqueak>>interpreterClassBuildITimerMultiThreadedAssert (in category 'cmake config build type ') -----
+ interpreterClassBuildITimerMultiThreadedAssert
+ 	"interpreter class can change to MultiThreaded for certain build types. For consistency sake, we maintain the pattern of other confiuration methods"
+ 	^self interpreterClassBuildITimerMultiThreaded
+ 
+ 
+ !

Item was added:
+ ----- Method: CPlatformConfigForSqueak>>interpreterClassBuildITimerMultiThreadedDebug (in category 'cmake config build type ') -----
+ interpreterClassBuildITimerMultiThreadedDebug
+ 	"interpreter class can change to MultiThreaded for certain build types. For consistency sake, we maintain the pattern of other confiuration methods"
+ 	^self interpreterClassBuildITimerMultiThreaded
+ 
+ 
+ !

Item was added:
+ ----- Method: CPlatformConfigForSqueak>>outputDir (in category 'squeak compatability') -----
+ outputDir
+ 
+ 	"the directory where built binaries will be stored"
+ 	^ outputDir ifNil: [ outputDir := (self topDir / self dirOutput /  self dirInstall) ]	
+ 
+ !

Item was changed:
+ ----- Method: CPlatformConfigForSqueak>>preferredIncludes (in category 'source files') -----
- ----- Method: CPlatformConfigForSqueak>>preferredIncludes (in category 'as yet unclassified') -----
  preferredIncludes
  	"^#() SystemNavigation default browseMethodsWhoseNamesContain: 'preferredIncludes'"
  
  	self subclassResponsibility
  	!

Item was added:
+ ----- 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 added:
+ ----- 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 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 added:
+ ----- Method: CPlatformConfigForSqueak>>setGlobalOptionsAfterDetermineSystem:buildType: (in category 'cmake config build type ') -----
+ setGlobalOptionsAfterDetermineSystem: aMaker buildType: aBuildType
+ 	"invoke correct setGlobalOptions for this buildType to allow per-buildType customization'"
+ 
+ 	|d |
+ 	d:= SqueakCMakeVMMakerAbstractBuilder default buildTypeAndDirectoryInfo copy.
+ 	d 
+ 		at: #build put: [self setGlobalOptionsAfterDetermineSystemBuild: aMaker];
+ 		at: #buildAssert  put: [self setGlobalOptionsAfterDetermineSystemBuildAssert: aMaker];
+ 		at: #buildAssertITimerHeartbeat  put: [self setGlobalOptionsAfterDetermineSystemBuildAssertITimerHeartbeat: aMaker];
+             at:#buildDebug  put: [self setGlobalOptionsAfterDetermineSystemBuildDebug: aMaker];   
+ 		at: #buildITimerHeartbeat  put: [self setGlobalOptionsAfterDetermineSystemBuildITimerHeartbeat: aMaker];
+ 		at: #buildMultiThreaded  put: [self setGlobalOptionsAfterDetermineSystemBuildMultiThreaded: aMaker ];
+ 		at: #buildMultiThreadedAssert  put: [self setGlobalOptionsAfterDetermineSystemBuildMultiThreadedAssert: aMaker];
+ 		at: #buildMultiThreadedDebug   put: [self setGlobalOptionsAfterDetermineSystemBuildMultiThreadedDebug: aMaker ];
+ 		at: #buildNone put:[self setGlobalOptionsBuildNone: aMaker].
+ 
+ 	 ^(d at: ( aBuildType)) value
+ !

Item was added:
+ ----- Method: CPlatformConfigForSqueak>>setupDirectories: (in category 'squeak compatability') -----
+ setupDirectories: aMaker
+ 	| dirsInclude |
+ 
+ 	" write the directories in separate include file"
+ 	dirsInclude := aMaker captureOutputDuring: [
+ 		aMaker
+ 			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'.
+ 	
+ 	aMaker include: 'directories.cmake'.
+ !

Item was added:
+ ----- Method: CPlatformConfigForSqueak>>srcDir (in category 'squeak compatability') -----
+ srcDir
+ 		^ srcDir ifNil: [ srcDir := (self topDir directoryNamed: 'src' )]!

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

Item was added:
+ ----- Method: CPlatformConfigForSqueak>>validateSourcesPresent (in category 'squeak compatability') -----
+ validateSourcesPresent
+ 	| sources |
+ 	sources := Smalltalk sourcesName.
+ 	
+ 	(sources == nil)
+ 		ifTrue: [	self error: 'VM source code cannot be generated without .sources file'.]		!

Item was added:
+ ----- Method: CPlatformConfigForSqueak>>write:toFile: (in category 'squeak compatability') -----
+ 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 removed:
- ----- Method: Linux32ARMv6StackV3CrossRaspbianConfig>>addDriver:sources:generator:externalLibs: (in category 'squeak compatibility') -----
- addDriver: name sources: aSources generator: cmakeGen externalLibs: extLibs
- 	super addDriver: name sources: aSources generator: cmakeGen externalLibs: extLibs
- !

Item was added:
+ ----- Method: Linux32ARMv6StackV3CrossRaspbianConfig>>cogitClass (in category 'source generation') -----
+ cogitClass
+ 	^ StackToRegisterMappingCogit 
+ !

Item was added:
+ ----- Method: Linux32ARMv6StackV3CrossRaspbianConfig>>interpreterClass (in category 'source generation') -----
+ interpreterClass
+ 	^ StackInterpreter!

Item was added:
+ ----- Method: Linux32ARMv6StackV3CrossRaspbianFastBltConfig>>cogitClass (in category 'source generation') -----
+ cogitClass
+ 	^ StackToRegisterMappingCogit 
+ !

Item was added:
+ ----- Method: Linux32ARMv6StackV3CrossRaspbianFastBltConfig>>interpreterClass (in category 'source generation') -----
+ interpreterClass
+ 	^ StackInterpreter!

Item was removed:
- ----- Method: Linux32ARMv6StackV3RaspbianConfig>>addDriver:sources:generator:externalLibs: (in category 'squeak compatibility') -----
- addDriver: name sources: aSources generator: cmakeGen externalLibs: extLibs
- 	super addDriver: name sources: aSources generator: cmakeGen externalLibs: extLibs
- !

Item was added:
+ ----- Method: Linux32ARMv6StackV3RaspbianConfig>>cogitClass (in category 'source generation') -----
+ cogitClass
+ 	^ StackToRegisterMappingCogit 
+ !

Item was added:
+ ----- Method: Linux32ARMv6StackV3RaspbianConfig>>interpreterClass (in category 'source generation') -----
+ interpreterClass
+ 	^ StackInterpreter!

Item was added:
+ ----- Method: Linux32ARMv6StackV3RaspbianFastBltConfig>>cogitClass (in category 'source generation') -----
+ cogitClass
+ 	^ StackToRegisterMappingCogit 
+ !

Item was added:
+ ----- Method: Linux32ARMv6StackV3RaspbianFastBltConfig>>interpreterClass (in category 'source generation') -----
+ interpreterClass
+ 	^ StackInterpreter!

Item was changed:
+ SqueakUnixConfig subclass: #Linux32x86Config
+ 	instanceVariableNames: ''
- CogFamilyUnixConfig subclass: #Linux32x86Config
- 	instanceVariableNames: 'buildType generateBuild generateBuildAssert generateBuildAssertITimerHeartbeat generateBuildDebug generateBuildDebugITimerHeartbeat generateBuildDebugMultiThreaded generateBuildIHeartbeatTimer generateBuildMultiThreaded generateBuildMultiThreadedAssert generateBuildMultiThreadedDebug'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'CMakeVMMakerSqueak-Linux32x86'!
  
  !Linux32x86Config commentStamp: 'tty 6/15/2014 14:02' prior: 0!
  A Linux32x86Config is a Squeak Compatibility Layer between the Pharo code in CMakeVMMaker and CMakeVMakerSqueak.
  
  I configure a VM according to my name's form: [Operating System] [WordSize] [Processor Language][VM MemoryManager][BuildType]Conf
  
  
  I am not meant to be built.
  
  SqueakLinux32x86Builder 
  	configureABuildFor: #ONE OF MY SUBCLASSES NAME HERE withBuildType: #build;
  	generateSources;
  	generate.  
  
  HelpBrowser openOn: CMakeVMMakerSqueakEndUserHelp
  HelpBrowser openOn: CMakeVMMakerSqueakDeveloperHelp
  
  !

Item was removed:
- ----- Method: Linux32x86Config>>addDriver:sources:generator:externalLibs: (in category 'squeak compatibility') -----
- addDriver: name sources: aSources generator: cmakeGen externalLibs: extLibs
- 
- 	| cfg srcs |
- 	
- 	srcs := aSources inject: '' into: [:res :each | res , ' "', each, '"' ].
- 	cfg := cmakeGen
- 		captureOutputDuring: [
- 			cmakeGen printHeader;
- 			project: name;
- 			include: '../directories.cmake';
- 		
- 			message: 'Adding module: ', name;
- 			
- 			addDefinitions:  self compilerFlags;
- 			addDefinitions: '-fPIC -DPIC';
- 			set: #sources to: srcs;
- 			cmd: 'add_library' params: name, ' SHARED ${sources}'; 
- 			includeDirectories: '${crossDir}/plugins/FilePlugin';
- 			includeDirectories: '${targetPlatform}/plugins/B3DAcceleratorPlugin';
- 			includeDirectories: '${crossDir}/plugins/B3DAcceleratorPlugin';
- 			set: 'LIBRARY_OUTPUT_PATH' toString: self outputDir fullName;
- 			addExternalLibraries: extLibs;
- 			cmd: 'target_link_libraries' params: name , ' ${LINKLIBS}';
- 			cmd: 'set_target_properties' params: name , ' PROPERTIES PREFIX "" SUFFIX "" 
- 			LINK_FLAGS -m32' 
- 	].
- 	
- 	(self buildDir / name) assureExistence.
- 	self write: cfg toFile: name , '/', cmakeGen outputFileName.
- 	cmakeGen addSubdirectory:  name.
- 	!

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

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

Item was removed:
- ----- Method: Linux32x86Config>>buildScript (in category 'squeak compatibility') -----
- buildScript
- 	"answer the build script for building everything"
- 	
- 
- 	^ 
- '#!!/usr/bin/env bash
- 
- cmake .
- make
- 
- '!

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

Item was removed:
- ----- Method: Linux32x86Config>>cogitClass (in category 'source generation') -----
- cogitClass
- 	^ StackToRegisterMappingCogit !

Item was removed:
- ----- Method: Linux32x86Config>>configH (in category 'squeak compatibility') -----
- configH
- 	" right now its like  that "
- 	^ '
- #ifndef __sq_config_h
- #define __sq_config_h
- 
- /* explicit image width */
- 
- #define HAVE_INTERP_H 1
- 
- /* package options */
- 
- #define USE_X11 1
- #define USE_X11_GLX 1
- /* #undef       USE_QUARTZ */
- /* #undef       USE_QUARTZ_CGL */
- /* #undef       USE_RFB */
- 
- /* libraries */
- 
- /* #undef       HAVE_LIBX11 */
- #define HAVE_LIBXEXT 1
- #define HAVE_LIBDL 1
- /* #undef       HAVE_DYLD */
- /* #undef       HAVE_LIBFFI */
- /* #undef       HAVE_ICONV */
- 
- /* #undef       USE_AUDIO_NONE */
- /* #undef       USE_AUDIO_SUN */
- /* #undef       USE_AUDIO_NAS */
- /* #undef       USE_AUDIO_OSS */
- /* #undef       USE_AUDIO_MACOSX */
- /* #undef       OSS_DEVICE */
- 
- /* header files */
- 
- #define HAVE_UNISTD_H 1
- /* #undef       NEED_GETHOSTNAME_P */
- 
- #define HAVE_DIRENT_H 1
- /* #undef       HAVE_SYS_NDIR_H */
- /* #undef       HAVE_SYS_DIR_H */
- /* #undef       HAVE_NDIR_H */
- #define HAVE_DLFCN_H 1
- /* #undef       HAVE_ICONV_H */
- 
- #define HAVE_SYS_TIME_H 1
- #define TIME_WITH_SYS_TIME 1
- 
- #define HAVE_SYS_FILIO_H 1
- 
- /* #undef       HAVE_SYS_AUDIOIO_H */
- /* #undef       HAVE_SUN_AUDIOIO_H */
- 
- /* #undef       HAVE_PTY_H */
- /* #undef       HAVE_UTIL_H */
- #define HAVE_LIBUTIL_H 1
- /* #undef       HAVE_STROPTS_H */
- 
- #define HAVE_GL_GL_H 1
- /* #undef       HAVE_OPENGL_GL_H */
- 
- /* #undef       NEED_SUNOS_H */
- 
- 
- #define HAVE_UUID_H
- /* system calls/library functions */
- 
- #define AT_EXIT atexit
- 
- #define HAVE_TZSET 1
- 
- #define HAVE_OPENPTY 1
- /* #undef       HAVE_UNIX98_PTYS */
- 
- #define HAVE_SNPRINTF 1
- /* #undef       HAVE___SNPRINTF */
- 
- #define HAVE_MMAP 1
- 
- /* #undef       HAVE_DYLD */
- 
- #define HAVE_LANGINFO_CODESET 1
- 
- #define HAVE_ALLOCA 1
- /* #undef       HAVE_ALLOCA_H */
- 
- #define HAVE_UNSETENV 1
- 
- #define HAVE_NANOSLEEP 1
- 
- /* widths of primitive types */
- 
- #define SIZEOF_INT 4
- #define SIZEOF_LONG 4
- #define SIZEOF_LONG_LONG 8
- #define SIZEOF_VOID_P 4
- 
- /* structures */
- 
- #define HAVE_TM_GMTOFF 1
- #define HAVE_TIMEZONE 1
- 
- /* typedefs */
- 
- /* #undef       size_t */
- /* #undef       socklen_t */
- 
- #define squeakInt64 long long
- 
- /* architecture */
- 
- #define OS_TYPE "unix"
- 
- #define VM_HOST "i386-freebsd8.2"
- #define VM_HOST_CPU "i386"
- /* #undef       VM_HOST_VENDOR */
- #define VM_HOST_OS "freebsd8.2"
- #define VM_BUILD_STRING "Unix built on "__DATE__ " "__TIME__" Compiler: "__VERSION__
- 
- /* #undef       WORDS_BIGENDIAN */
- /* #undef       DOUBLE_WORD_ALIGNMENT */
- 
- /* damage containment */
- 
- /* #undef       DARWIN */
- 
- #ifdef NEED_SUNOS_H
- # include "sunos.h"
- #endif
- 
- /* other configured variables */
- 
- #define SQ_VERSION "3.9a-7024"
- #define VM_VERSION "3.9-7"
- #define VM_MODULE_PREFIX ""
- /* #undef VM_DLSYM_PREFIX */
- #define VM_X11DIR "/usr/X11R6/lib"
- 
- /* avoid dependencies on glibc2.3 */
- 
- /* #undef HAVE_FEATURES_H */
- 
- #if defined(HAVE_FEATURES_H)
- # include "glibc.h"
- #endif
- 
- #endif /* __sq_config_h */
- 																																																																					
- 																																																																				'!

Item was changed:
  ----- Method: Linux32x86Config>>executableName (in category 'accessing') -----
  executableName
+ 	self subclassResponsibility!
- 	self required!

Item was removed:
- ----- Method: Linux32x86Config>>executableType (in category 'accessing') -----
- executableType
- 	^''
- 
- "
- SystemNavigation default browseMethodsWhoseNamesContain: ''executableType''
- 	^ 'MACOSX_BUNDLE'
- 	^ 'WIN32'\
- 	^ ''
- "!

Item was removed:
- ----- Method: Linux32x86Config>>generate (in category 'squeak compatibility') -----
- generate
- 	self generatePluginsList. 
- 	self generateLicense. 
- 	^ CMakeVMGeneratorForSqueak generate: self !

Item was removed:
- ----- Method: Linux32x86Config>>outputDir (in category 'squeak compatibility') -----
- outputDir
- 
- 	"the directory where built binaries will be stored"
- 	^ outputDir ifNil: [ outputDir := (self topDir / self dirOutput /  self dirInstall) ]	
- 
- !

Item was removed:
- ----- Method: Linux32x86Config>>prepareVMMaker (in category 'squeak compatibility') -----
- 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 removed:
- ----- Method: Linux32x86Config>>setupDirectories: (in category 'squeak compatibility') -----
- 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 removed:
- ----- Method: Linux32x86Config>>srcDir (in category 'squeak compatibility') -----
- srcDir
- 		^ srcDir ifNil: [ srcDir := (self topDir directoryNamed: 'src' )]!

Item was removed:
- ----- 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 removed:
- ----- Method: Linux32x86Config>>validateSourcesPresent (in category 'squeak compatibility') -----
- validateSourcesPresent
- 	| sources |
- 	sources := Smalltalk sourcesName.
- 	
- 	(sources == nil)
- 		ifTrue: [	self error: 'VM source code cannot be generated without .sources file'.]		!

Item was removed:
- ----- Method: Linux32x86Config>>write:toFile: (in category 'squeak compatibility') -----
- 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 added:
+ ----- Method: Linux32x86NewspeakCogSpurConfig>>cogitClass (in category 'source generation') -----
+ cogitClass
+ 	^ StackToRegisterMappingCogit 
+ !

Item was added:
+ ----- Method: Linux32x86NewspeakCogSpurConfig>>interpreterClass (in category 'source generation') -----
+ interpreterClass
+ 	^ CoInterpreter
+ !

Item was removed:
- ----- Method: Linux32x86NewspeakCogSpurConfig>>prepareForGeneration (in category 'source generation') -----
- prepareForGeneration
- 	^ self prepareForCogGeneration
- !

Item was added:
+ ----- Method: Linux32x86NewspeakCogV3Config>>cogitClass (in category 'source generation') -----
+ cogitClass
+ 	^ StackToRegisterMappingCogit 
+ !

Item was added:
+ ----- Method: Linux32x86NewspeakCogV3Config>>interpreterClass (in category 'source generation') -----
+ interpreterClass
+ 	^ CoInterpreter
+ !

Item was removed:
- ----- Method: Linux32x86NewspeakCogV3Config>>prepareForGeneration (in category 'source generation') -----
- prepareForGeneration
- 	^ self prepareForCogGeneration
- !

Item was added:
+ ----- Method: Linux32x86NewspeakSistaSpurConfig>>cogitClass (in category 'source generation') -----
+ cogitClass
+ 	^SistaStackToRegisterMappingCogit
+ !

Item was added:
+ ----- Method: Linux32x86NewspeakSistaSpurConfig>>interpreterClass (in category 'source generation') -----
+ interpreterClass
+ 	^ CoInterpreter
+ !

Item was added:
+ ----- Method: Linux32x86NewspeakSistaV3Config>>cogitClass (in category 'source generation') -----
+ cogitClass
+ 	^SistaStackToRegisterMappingCogit
+ !

Item was added:
+ ----- Method: Linux32x86NewspeakSistaV3Config>>interpreterClass (in category 'source generation') -----
+ interpreterClass
+ 	^ CoInterpreter
+ !

Item was added:
+ ----- Method: Linux32x86NewspeakStackSpurConfig>>cogitClass (in category 'source generation') -----
+ cogitClass
+ 	^ StackToRegisterMappingCogit 
+ !

Item was added:
+ ----- Method: Linux32x86NewspeakStackSpurConfig>>interpreterClass (in category 'source generation') -----
+ interpreterClass
+ 	^ StackInterpreter!

Item was added:
+ ----- Method: Linux32x86NewspeakStackV3Config>>cogitClass (in category 'source generation') -----
+ cogitClass
+ 	^ StackToRegisterMappingCogit 
+ !

Item was added:
+ ----- Method: Linux32x86NewspeakStackV3Config>>interpreterClass (in category 'source generation') -----
+ interpreterClass
+ 	^ StackInterpreter!

Item was added:
+ ----- Method: Linux32x86SqueakCogSpurConfig>>cogitClass (in category 'source generation') -----
+ cogitClass
+ 	^ StackToRegisterMappingCogit 
+ !

Item was added:
+ ----- Method: Linux32x86SqueakCogSpurConfig>>interpreterClass (in category 'source generation') -----
+ interpreterClass
+ 	^ CoInterpreter
+ !

Item was removed:
- ----- Method: Linux32x86SqueakCogSpurConfig>>prepareForGeneration (in category 'source generation') -----
- prepareForGeneration
- 	^ self prepareForCogGeneration
- !

Item was removed:
- ----- Method: Linux32x86SqueakCogV3Config>>prepareForGeneration (in category 'source generation') -----
- prepareForGeneration
- 	^ self prepareForCogGeneration
- !

Item was changed:
+ SqueakUnixConfig subclass: #Linux32x86SqueakCogV3Configz
+ 	instanceVariableNames: ''
- CogFamilyUnixConfig subclass: #Linux32x86SqueakCogV3Configz
- 	instanceVariableNames: 'buildType generateBuild generateBuildAssert generateBuildAssertITimerHeartbeat generateBuildDebug generateBuildDebugITimerHeartbeat generateBuildDebugMultiThreaded generateBuildIHeartbeatTimer generateBuildMultiThreaded generateBuildMultiThreadedAssert generateBuildMultiThreadedDebug'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'CMakeVMMakerSqueak-IslandOfMisfitToys'!
  
  !Linux32x86SqueakCogV3Configz 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
  !

Item was removed:
- ----- Method: Linux32x86SqueakCogV3Configz>>addDriver:sources:generator:externalLibs: (in category 'squeak compatibility') -----
- addDriver: name sources: aSources generator: cmakeGen externalLibs: extLibs
- 
- 	| cfg srcs |
- 	
- 	srcs := aSources inject: '' into: [:res :each | res , ' "', each, '"' ].
- 	cfg := cmakeGen
- 		captureOutputDuring: [
- 			cmakeGen printHeader;
- 			project: name;
- 			include: '../directories.cmake';
- 		
- 			message: 'Adding module: ', name;
- 			
- 			addDefinitions:  self compilerFlags;
- 			addDefinitions: '-fPIC -DPIC';
- 			set: #sources to: srcs;
- 			cmd: 'add_library' params: name, ' SHARED ${sources}'; 
- 			includeDirectories: '${crossDir}/plugins/FilePlugin';
- 			includeDirectories: '${targetPlatform}/plugins/B3DAcceleratorPlugin';
- 			includeDirectories: '${crossDir}/plugins/B3DAcceleratorPlugin';
- 			set: 'LIBRARY_OUTPUT_PATH' toString: self outputDir fullName;
- 			addExternalLibraries: extLibs;
- 			cmd: 'target_link_libraries' params: name , ' ${LINKLIBS}';
- 			cmd: 'set_target_properties' params: name , ' PROPERTIES PREFIX "" SUFFIX "" 
- 			LINK_FLAGS -m32' 
- 	].
- 	
- 	(self buildDir / name) assureExistence.
- 	self write: cfg toFile: name , '/', cmakeGen outputFileName.
- 	cmakeGen addSubdirectory:  name.
- 	!

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

Item was removed:
- ----- Method: Linux32x86SqueakCogV3Configz>>buildDirName (in category 'squeak compatibility') -----
- buildDirName
- 	^ 'cmake_build.linux32x86'!

Item was removed:
- ----- Method: Linux32x86SqueakCogV3Configz>>buildScript (in category 'build script') -----
- buildScript
- 	"answer the build script for building everything"
- 	
- 
- 	^ 
- '#!!/usr/bin/env bash
- 
- cmake .
- make
- 
- '!

Item was removed:
- ----- Method: Linux32x86SqueakCogV3Configz>>buildType: (in category 'squeak compatibility') -----
- buildType: aSymbol
- 	buildType:= aSymbol!

Item was removed:
- ----- Method: Linux32x86SqueakCogV3Configz>>compilerFlags (in category 'squeak compatibility') -----
- compilerFlags
- 	|d commonFlags flags|
- 	d:= SqueakCMakeVMMakerAbstractBuilder default buildTypeAndDirectoryInfo copy.
- 	d 
- 		at: #build put: [self compilerFlagsBuild];
- 		at: #buildAssert  put: [self compilerFlagsAssert];
- 		at: #buildAssertITimerHeartbeat  put: [self compilerFlagsAssertITimerHeartbeat];
-             at:#buildDebug  put: [self compilerFlagsDebug];   "located in CMakeVMMaker CPlatformConfig"
- 		at: #buildDebugITimerHeartbeat  put: [self compilerFlagsDebugITimerHeartbeat ];
- 		at: #buildITimerHeartbeat  put: [self compilerFlagsIHeartbeatTimer];
- 		at: #buildMultiThreaded  put: [self compilerFlagsMultiThreaded ];
- 		at: #buildMultiThreadedAssert  put: [self compilerFlagsMultiThreadedAssert];
- 		at: #buildMultiThreadedDebug   put: [self compilerFlagsMultiThreadedDebug ];
- 		at: #buildNone put:[self compilerFlagsNoBuildType].
- 
-     flags:= String streamContents: [ :stream |
- 	 (((d at:  buildType) value)  collect: #withBlanksTrimmed as: Set)
- 		asStringOn: stream 
- 		delimiter:' '].
- 
-     commonFlags:=String streamContents: [ :stream |
- 		((self commonCompilerFlags) collect: #withBlanksTrimmed as: Set)
- 			asStringOn: stream 
- 			delimiter: ' ' ].
- 	^ commonFlags, ' ' ,flags.!

Item was removed:
- ----- Method: Linux32x86SqueakCogV3Configz>>dirFrom: (in category 'squeak compatibility') -----
- dirFrom: t1 
- 	^ t1 isString
- 		ifTrue: [FileDirectory forFileName: t1]
- 		ifFalse: [t1]!

Item was changed:
  ----- Method: Linux32x86SqueakCogV3Configz>>executableName (in category 'accessing') -----
  executableName
+ 	^ self vmCogExecutableName!
- 	^ 'CogVM'!

Item was removed:
- ----- Method: Linux32x86SqueakCogV3Configz>>generate (in category 'accessing') -----
- generate 
- 	self generatePluginsList. 
- 	self generateLicense. 
- 	"^super generate"
- 	^CMakeVMGeneratorForSqueak generate:self    "Bypass CPlatformConfig generate to invoke our compatibility class"!

Item was removed:
- ----- Method: Linux32x86SqueakCogV3Configz>>generateLicense (in category 'accessing') -----
- generateLicense 
- 	self 
- 		write:  (self class licenseTemplate 
- 			format: { self version })
- 		toFile: 'LICENSE.txt'
- 	!

Item was removed:
- ----- Method: Linux32x86SqueakCogV3Configz>>generatePluginsList (in category 'accessing') -----
- generatePluginsList 
- 	self 
- 		write:  (self class pluginsTemplate 
- 			format: {
- 				self version. 
- 				String streamContents: [ :stream | self internalPlugins asStringOn: stream delimiter: String cr ].
- 				String streamContents: [ :stream | self externalPlugins asStringOn: stream delimiter: String cr ].
- 				self executableName })
- 		toFile: 'PLUGINS.txt'
- 	!

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

Item was removed:
- ----- Method: Linux32x86SqueakCogV3Configz>>prepareForGeneration (in category 'source generation') -----
- prepareForGeneration
- 	^ self prepareForCogGeneration
- !

Item was removed:
- ----- Method: Linux32x86SqueakCogV3Configz>>prepareVMMaker (in category 'squeak compatibility') -----
- 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 removed:
- ----- Method: Linux32x86SqueakCogV3Configz>>setupDirectories: (in category 'squeak compatibility') -----
- 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 removed:
- ----- Method: Linux32x86SqueakCogV3Configz>>srcDir (in category 'squeak compatibility') -----
- srcDir
- 		^ srcDir ifNil: [ srcDir := (self topDir directoryNamed: 'src' )]!

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

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

Item was removed:
- ----- Method: Linux32x86SqueakCogV3Configz>>version (in category 'accessing') -----
- version
- 	^ ''!

Item was removed:
- ----- Method: Linux32x86SqueakCogV3Configz>>write:toFile: (in category 'squeak compatibility') -----
- 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 added:
+ ----- Method: Linux32x86SqueakCogV3DebugConfigz>>cogitClass (in category 'source generation') -----
+ cogitClass
+ 	^ StackToRegisterMappingCogit 
+ !

Item was added:
+ ----- Method: Linux32x86SqueakCogV3DebugConfigz>>interpreterClass (in category 'source generation') -----
+ interpreterClass
+ 	^ CoInterpreter!

Item was removed:
- ----- Method: Linux32x86SqueakCogV3MultiThreadedConfigz>>buildDirName (in category 'squeak compatibility') -----
- buildDirName
- 	^ 'cmake_unixbuild/mtbld'!

Item was added:
+ ----- Method: Linux32x86SqueakCogV3MultiThreadedConfigz>>cogitClass (in category 'source generation') -----
+ cogitClass
+ 	^ StackToRegisterMappingCogit 
+ !

Item was changed:
  ----- Method: Linux32x86SqueakCogV3MultiThreadedConfigz>>executableName (in category 'accessing') -----
  executableName
+ 	^ self vmCogExecutableName!
- 	^ 'CogMTVM'!

Item was added:
+ ----- Method: Linux32x86SqueakSistaSpurConfig>>cogitClass (in category 'source generation') -----
+ cogitClass
+ 	^SistaStackToRegisterMappingCogit
+ !

Item was added:
+ ----- Method: Linux32x86SqueakSistaSpurConfig>>interpreterClass (in category 'source generation') -----
+ interpreterClass
+ 	^ CoInterpreter
+ !

Item was added:
+ ----- Method: Linux32x86SqueakSistaV3Config>>cogitClass (in category 'source generation') -----
+ cogitClass
+ 	^SistaStackToRegisterMappingCogit
+ !

Item was added:
+ ----- Method: Linux32x86SqueakSistaV3Config>>interpreterClass (in category 'source generation') -----
+ interpreterClass
+ 	^ CoInterpreter
+ !

Item was added:
+ ----- Method: Linux32x86SqueakStackSpurConfig>>cogitClass (in category 'source generation') -----
+ cogitClass
+ 	^ StackToRegisterMappingCogit 
+ !

Item was added:
+ ----- Method: Linux32x86SqueakStackSpurConfig>>interpreterClass (in category 'source generation') -----
+ interpreterClass
+ 	^ StackInterpreter!

Item was changed:
+ SqueakUnixConfig subclass: #Linux32x86SqueakStackSpurConfigz
+ 	instanceVariableNames: ''
- CPlatformConfigForSqueak subclass: #Linux32x86SqueakStackSpurConfigz
- 	instanceVariableNames: 'buildType'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'CMakeVMMakerSqueak-IslandOfMisfitToys'!

Item was added:
+ ----- Method: Linux32x86SqueakStackSpurConfigz>>cogitClass (in category 'source generation') -----
+ cogitClass
+ 	^ StackToRegisterMappingCogit 
+ !

Item was added:
+ ----- Method: Linux32x86SqueakStackSpurConfigz>>interpreterClass (in category 'source generation') -----
+ interpreterClass
+ 	^ StackInterpreter!

Item was added:
+ ----- Method: Linux32x86SqueakStackV3Config>>cogitClass (in category 'source generation') -----
+ cogitClass
+ 	^ StackToRegisterMappingCogit 
+ !

Item was added:
+ ----- Method: Linux32x86SqueakStackV3Config>>interpreterClass (in category 'source generation') -----
+ interpreterClass
+ 	^ StackInterpreter!

Item was changed:
+ SqueakUnixConfig subclass: #Linux32x86SqueakStackV3Configz
+ 	instanceVariableNames: ''
- StackUnixConfig subclass: #Linux32x86SqueakStackV3Configz
- 	instanceVariableNames: 'buildType generateBuild generateBuildAssert generateBuildAssertITimerHeartbeat generateBuildDebug generateBuildDebugITimerHeartbeat generateBuildDebugMultiThreaded generateBuildIHeartbeatTimer generateBuildMultiThreaded generateBuildMultiThreadedAssert generateBuildMultiThreadedDebug'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'CMakeVMMakerSqueak-IslandOfMisfitToys'!
  
+ !Linux32x86SqueakStackV3Configz commentStamp: 'tty 6/18/2014 09:45' prior: 0!
+ NOTE: TTY. this used to subclass StackUnixConfig in pharo. 
+ 
- !Linux32x86SqueakStackV3Configz 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
  !

Item was removed:
- ----- Method: Linux32x86SqueakStackV3Configz>>addDriver:sources:generator:externalLibs: (in category 'squeak compatibility') -----
- addDriver: name sources: aSources generator: cmakeGen externalLibs: extLibs
- 
- 	| cfg srcs |
- 	
- 	srcs := aSources inject: '' into: [:res :each | res , ' "', each, '"' ].
- 	cfg := cmakeGen
- 		captureOutputDuring: [
- 			cmakeGen printHeader;
- 			project: name;
- 			include: '../directories.cmake';
- 		
- 			message: 'Adding module: ', name;
- 			
- 			addDefinitions:  self compilerFlags;
- 			addDefinitions: '-fPIC -DPIC';
- 			set: #sources to: srcs;
- 			cmd: 'add_library' params: name, ' SHARED ${sources}'; 
- 			includeDirectories: '${crossDir}/plugins/FilePlugin';
- 			includeDirectories: '${targetPlatform}/plugins/B3DAcceleratorPlugin';
- 			includeDirectories: '${crossDir}/plugins/B3DAcceleratorPlugin';
- 			set: 'LIBRARY_OUTPUT_PATH' toString: self outputDir fullName;
- 			addExternalLibraries: extLibs;
- 			cmd: 'target_link_libraries' params: name , ' ${LINKLIBS}';
- 			cmd: 'set_target_properties' params: name , ' PROPERTIES PREFIX "" SUFFIX "" 
- 			LINK_FLAGS -m32' 
- 	].
- 	
- 	(self buildDir / name) assureExistence.
- 	self write: cfg toFile: name , '/', cmakeGen outputFileName.
- 	cmakeGen addSubdirectory:  name.
- 	!

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

Item was removed:
- ----- Method: Linux32x86SqueakStackV3Configz>>buildDirName (in category 'squeak compatibility') -----
- buildDirName
- 	^ 'cmake_stackbuild/unixbuild/bld'!

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

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

Item was removed:
- ----- Method: Linux32x86SqueakStackV3Configz>>buildType: (in category 'squeak compatibility') -----
- buildType: aSymbol
- 	buildType:= aSymbol!

Item was added:
+ ----- Method: Linux32x86SqueakStackV3Configz>>cogitClass (in category 'source generation') -----
+ cogitClass
+ 	^ StackToRegisterMappingCogit 
+ !

Item was removed:
- ----- Method: Linux32x86SqueakStackV3Configz>>compilerFlags (in category 'squeak compatibility') -----
- compilerFlags
- 	|d commonFlags flags|
- 	d:= SqueakCMakeVMMakerAbstractBuilder default buildTypeAndDirectoryInfo copy.
- 	d 
- 		at: #build put: [self compilerFlagsBuild];
- 		at: #buildAssert  put: [self compilerFlagsAssert];
- 		at: #buildAssertITimerHeartbeat  put: [self compilerFlagsAssertITimerHeartbeat];
-             at:#buildDebug  put: [self compilerFlagsDebug];   "located in CMakeVMMaker CPlatformConfig"
- 		at: #buildDebugITimerHeartbeat  put: [self compilerFlagsDebugITimerHeartbeat ];
- 		at: #buildITimerHeartbeat  put: [self compilerFlagsIHeartbeatTimer];
- 		at: #buildMultiThreaded  put: [self compilerFlagsMultiThreaded ];
- 		at: #buildMultiThreadedAssert  put: [self compilerFlagsMultiThreadedAssert];
- 		at: #buildMultiThreadedDebug   put: [self compilerFlagsMultiThreadedDebug ];
- 		at: #buildNone put:[self compilerFlagsNoBuildType].
- 
-     flags:= String streamContents: [ :stream |
- 	 (((d at:  buildType) value)  collect: #withBlanksTrimmed as: Set)
- 		asStringOn: stream 
- 		delimiter:' '].
- 
-     commonFlags:=String streamContents: [ :stream |
- 		((self commonCompilerFlags) collect: #withBlanksTrimmed as: Set)
- 			asStringOn: stream 
- 			delimiter: ' ' ].
- 	^ commonFlags, ' ' ,flags.!

Item was changed:
  ----- Method: Linux32x86SqueakStackV3Configz>>executableName (in category 'accessing') -----
  executableName
+ 	^ self vmStackExecutableName!
- 	^ 'StackVM'!

Item was removed:
- ----- Method: Linux32x86SqueakStackV3Configz>>generate (in category 'public') -----
- generate 
- 	self generatePluginsList. 
- 	self generateLicense. 
- 	"^super generate"
- 	^CMakeVMGeneratorForSqueak generate:self    "Bypass CPlatformConfig generate to invoke our compatibility class"!

Item was removed:
- ----- Method: Linux32x86SqueakStackV3Configz>>generateLicense (in category 'public') -----
- generateLicense 
- 	self 
- 		write:  (self class licenseTemplate 
- 			format: { self version })
- 		toFile: 'LICENSE.txt'
- 	!

Item was removed:
- ----- Method: Linux32x86SqueakStackV3Configz>>generatePluginsList (in category 'public') -----
- generatePluginsList 
- 	self 
- 		write:  (self class pluginsTemplate 
- 			format: {
- 				self version. 
- 				String streamContents: [ :stream | self internalPlugins asStringOn: stream delimiter: String cr ].
- 				String streamContents: [ :stream | self externalPlugins asStringOn: stream delimiter: String cr ].
- 				self executableName })
- 		toFile: 'PLUGINS.txt'
- 	!

Item was added:
+ ----- Method: Linux32x86SqueakStackV3Configz>>interpreterClass (in category 'source generation') -----
+ interpreterClass
+ 	^ StackInterpreter!

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

Item was removed:
- ----- Method: Linux32x86SqueakStackV3Configz>>prepareVMMaker (in category 'squeak compatibility') -----
- 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 removed:
- ----- Method: Linux32x86SqueakStackV3Configz>>setupDirectories: (in category 'squeak compatibility') -----
- 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 removed:
- ----- Method: Linux32x86SqueakStackV3Configz>>srcDir (in category 'squeak compatibility') -----
- srcDir
- 		^ srcDir ifNil: [ srcDir := (self topDir directoryNamed: 'stacksrc' )]!

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

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

Item was removed:
- ----- Method: Linux32x86SqueakStackV3Configz>>write:toFile: (in category 'squeak compatibility') -----
- 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 added:
+ ----- Method: Linux32x86SqueakStackV3DebugConfigz>>cogitClass (in category 'source generation') -----
+ cogitClass
+ 	^ StackToRegisterMappingCogit 
+ !

Item was added:
+ ----- Method: Linux32x86SqueakStackV3DebugConfigz>>interpreterClass (in category 'source generation') -----
+ interpreterClass
+ 	^ StackInterpreter!

Item was added:
+ ----- Method: Linux32x86SqueakStackV3FixedVerSIConfig>>cogitClass (in category 'source generation') -----
+ cogitClass
+ 	^ StackToRegisterMappingCogit 
+ !

Item was added:
+ ----- Method: Linux32x86SqueakStackV3FixedVerSIConfig>>interpreterClass (in category 'source generation') -----
+ interpreterClass
+ 	^ StackInterpreter!

Item was changed:
+ SqueakUnixConfig subclass: #Linux64Config
+ 	instanceVariableNames: ''
- CogFamilyUnixConfig subclass: #Linux64Config
- 	instanceVariableNames: 'buildType generateBuild generateBuildAssert generateBuildAssertITimerHeartbeat generateBuildDebug generateBuildDebugITimerHeartbeat generateBuildDebugMultiThreaded generateBuildIHeartbeatTimer generateBuildMultiThreaded generateBuildMultiThreadedAssert generateBuildMultiThreadedDebug'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'CMakeVMMakerSqueak-LinuxX86-64'!
  
  !Linux64Config commentStamp: 'tty 6/15/2014 14:01' prior: 0!
  I configure a VM according to my name's form: [Operating System] [WordSize] [Processor Language][VM MemoryManager][BuildType]Conf
  
  
  I am not meant to be built.
  
  SqueakLinux32x86_64Builder 
  	configureABuildFor: #ONE OF MY SUBCLASSES NAME HERE withBuildType: #build;
  	generateSources;
  	generate.  
  
  HelpBrowser openOn: CMakeVMMakerSqueakEndUserHelp
  HelpBrowser openOn: CMakeVMMakerSqueakDeveloperHelp
  !

Item was removed:
- ----- Method: Linux64Config>>addDriver:sources:generator:externalLibs: (in category 'squeak compatibility') -----
- addDriver: name sources: aSources generator: cmakeGen externalLibs: extLibs
- 
- 	| cfg srcs |
- 	
- 	srcs := aSources inject: '' into: [:res :each | res , ' "', each, '"' ].
- 	cfg := cmakeGen
- 		captureOutputDuring: [
- 			cmakeGen printHeader;
- 			project: name;
- 			include: '../directories.cmake';
- 		
- 			message: 'Adding module: ', name;
- 			
- 			addDefinitions:  self compilerFlags;
- 			addDefinitions: '-fPIC -DPIC';
- 			set: #sources to: srcs;
- 			cmd: 'add_library' params: name, ' SHARED ${sources}'; 
- 			includeDirectories: '${crossDir}/plugins/FilePlugin';
- 			includeDirectories: '${targetPlatform}/plugins/B3DAcceleratorPlugin';
- 			includeDirectories: '${crossDir}/plugins/B3DAcceleratorPlugin';
- 			set: 'LIBRARY_OUTPUT_PATH' toString: self outputDir fullName;
- 			addExternalLibraries: extLibs;
- 			cmd: 'target_link_libraries' params: name , ' ${LINKLIBS}';
- 			cmd: 'set_target_properties' params: name , ' PROPERTIES PREFIX "" SUFFIX "" 
- 			LINK_FLAGS -m32' 
- 	].
- 	
- 	(self buildDir / name) assureExistence.
- 	self write: cfg toFile: name , '/', cmakeGen outputFileName.
- 	cmakeGen addSubdirectory:  name.
- 	!

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

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

Item was removed:
- ----- Method: Linux64Config>>buildScript (in category 'squeak compatibility') -----
- buildScript
- 	"answer the build script for building everything"
- 	
- 
- 	^ 
- '#!!/usr/bin/env bash
- 
- cmake .
- make
- 
- '!

Item was removed:
- ----- Method: Linux64Config>>buildType: (in category 'squeak compatibility') -----
- buildType: aSymbol
- 	buildType:= aSymbol!

Item was removed:
- ----- Method: Linux64Config>>cogitClass (in category 'squeak compatibility') -----
- cogitClass
- 	"answer a class for machine code generation or nil"
- 	
- 	^ StackToRegisterMappingCogit !

Item was removed:
- ----- Method: Linux64Config>>commonCompilerFlags (in category 'squeak compatibility') -----
- commonCompilerFlags
- 
- 	"Common compiler flags
- 	
- 	
- 	LSB_FIRST=1 means that target platform is little endian. 
- 	set it to 0 for big-endian platforms
- 	
- 	"
- 	
- 	^ {
- 		'-DLSB_FIRST=1'. 
- 		'-DUSE_GLOBAL_STRUCT=0'. 
- 		'-DCOGMTVM=0'. 
- 		'-m32'.
- 		'-DENABLE_FAST_BLT ' } 	
- 	!

Item was removed:
- ----- Method: Linux64Config>>compilerFlags (in category 'squeak compatibility') -----
- compilerFlags
- 	|d commonFlags flags|
- 	d:= SqueakCMakeVMMakerAbstractBuilder default buildTypeAndDirectoryInfo copy.
- 	d 
- 		at: #build put: [self compilerFlagsBuild];
- 		at: #buildAssert  put: [self compilerFlagsAssert];
- 		at: #buildAssertITimerHeartbeat  put: [self compilerFlagsAssertITimerHeartbeat];
-             at:#buildDebug  put: [self compilerFlagsDebug];   "located in CMakeVMMaker CPlatformConfig"
- 		at: #buildDebugITimerHeartbeat  put: [self compilerFlagsDebugITimerHeartbeat ];
- 		at: #buildITimerHeartbeat  put: [self compilerFlagsIHeartbeatTimer];
- 		at: #buildMultiThreaded  put: [self compilerFlagsMultiThreaded ];
- 		at: #buildMultiThreadedAssert  put: [self compilerFlagsMultiThreadedAssert];
- 		at: #buildMultiThreadedDebug   put: [self compilerFlagsMultiThreadedDebug ];
- 		at: #buildNone put:[self compilerFlagsNoBuildType].
- 
-     flags:= String streamContents: [ :stream |
- 	 (((d at:  buildType) value)  collect: #withBlanksTrimmed as: Set)
- 		asStringOn: stream 
- 		delimiter:' '].
- 
-     commonFlags:=String streamContents: [ :stream |
- 		((self commonCompilerFlags) collect: #withBlanksTrimmed as: Set)
- 			asStringOn: stream 
- 			delimiter: ' ' ].
- 	^ commonFlags, ' ' ,flags.!

Item was removed:
- ----- Method: Linux64Config>>dirFrom: (in category 'squeak compatibility') -----
- dirFrom: aStringOrDir
- 	^ aStringOrDir isString
- 		ifTrue: [ FileDirectory forFileName: aStringOrDir  ]
- 		ifFalse: [ aStringOrDir ]!

Item was removed:
- ----- Method: Linux64Config>>outputDir (in category 'squeak compatibility') -----
- outputDir
- 
- 	"the directory where built binaries will be stored"
- 	^ outputDir ifNil: [ outputDir := (self topDir / self dirOutput / self dirInstall) ]	
- 
- !

Item was removed:
- ----- Method: Linux64Config>>prepareVMMaker (in category 'squeak compatibility') -----
- 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 removed:
- ----- Method: Linux64Config>>setupDirectories: (in category 'cmake config build type ') -----
- setupDirectories: aMaker 
- 	"SystemNavigation default browseMethodsWhoseNamesContain: 'setupDirectories:'
- 	
- 	we subclass this in our concrete builder and route it to 
- 	
- 	^self setupDirectories: aMaker buildType: (self buildType asSymbol)
- 
- 	"
- 	self required
- 	
- !

Item was removed:
- ----- Method: Linux64Config>>srcDir (in category 'squeak compatibility') -----
- srcDir
- 		^ srcDir ifNil: [ srcDir := (self topDir directoryNamed: 'src' )]!

Item was removed:
- ----- Method: Linux64Config>>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 removed:
- ----- Method: Linux64Config>>validateSourcesPresent (in category 'squeak compatibility') -----
- validateSourcesPresent
- 	| sources |
- 	sources := Smalltalk sourcesName.
- 	
- 	(sources == nil)
- 		ifTrue: [	self error: 'VM source code cannot be generated without .sources file'.]		!

Item was removed:
- ----- Method: Linux64Config>>write:toFile: (in category 'squeak compatibility') -----
- 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:
  Linux64Config subclass: #Linux64NewspeakCogSpur
  	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'CMakeVMMakerSqueak-LinuxX86-64'!
  
+ !Linux64NewspeakCogSpur commentStamp: '<historical>' prior: 0!
- !Linux64NewspeakCogSpur commentStamp: 'tty 6/15/2014 14:01' prior: 0!
  I configure a VM according to my name's form: [Operating System] [WordSize] [Processor Language][VM MemoryManager][BuildType]Conf
  
  
  SqueakLinux32x86_64Builder 
  	configureABuildFor: #MY  NAME HERE withBuildType: #build;
  	generateSources;
  	generate.  
  
  HelpBrowser openOn: CMakeVMMakerSqueakEndUserHelp
+ HelpBrowser openOn: CMakeVMMakerSqueakDeveloperHelp!
- HelpBrowser openOn: CMakeVMMakerSqueakDeveloperHelp
- !

Item was changed:
  ----- Method: Linux64NewspeakCogSpur>>availableBuilds (in category 'cmake') -----
  availableBuilds
  	^SqueakCMakeVMMakerAbstractBuilder default noBuildConfigurations!

Item was added:
+ ----- Method: Linux64NewspeakCogSpur>>cogitClass (in category 'source generation') -----
+ cogitClass
+ 	^ StackToRegisterMappingCogit 
+ !

Item was changed:
  ----- Method: Linux64NewspeakCogSpur>>dirBuildLanguageVMMM (in category 'cmake') -----
  dirBuildLanguageVMMM
  	^self newspeakCogSpur!

Item was removed:
- ----- Method: Linux64NewspeakCogSpur>>dirBuildPlatform (in category 'cmake') -----
- dirBuildPlatform
- 	"the directory for the platform. example: build.linux32x86"
- 	^self dirLinux32x8664!

Item was changed:
  ----- Method: Linux64NewspeakCogSpur>>excludeFromBuild (in category 'cmake') -----
  excludeFromBuild
  	"over-ride to exclude yourself from a build or not"
  	^true!

Item was changed:
  ----- Method: Linux64NewspeakCogSpur>>executableName (in category 'cmake') -----
  executableName
  	^ self vmCogExecutableName!

Item was added:
+ ----- Method: Linux64NewspeakCogSpur>>interpreterClass (in category 'source generation') -----
+ interpreterClass
+ 	^ CoInterpreter
+ !

Item was added:
+ ----- Method: Linux64NewspeakCogV3>>cogitClass (in category 'source generation') -----
+ cogitClass
+ 	^ StackToRegisterMappingCogit 
+ !

Item was removed:
- ----- Method: Linux64NewspeakCogV3>>dirBuildPlatform (in category 'cmake') -----
- dirBuildPlatform
- 	"the directory for the platform. example: build.linux32x86"
- 	^self dirLinux32x8664!

Item was added:
+ ----- Method: Linux64NewspeakCogV3>>interpreterClass (in category 'source generation') -----
+ interpreterClass
+ 	^ CoInterpreter
+ !

Item was added:
+ ----- Method: Linux64NewspeakSistaSpur>>cogitClass (in category 'source generation') -----
+ cogitClass
+ 	^SistaStackToRegisterMappingCogit
+ !

Item was removed:
- ----- Method: Linux64NewspeakSistaSpur>>dirBuildPlatform (in category 'cmake') -----
- dirBuildPlatform
- 	"the directory for the platform. example: build.linux32x86"
- 	^self dirLinux32x8664!

Item was added:
+ ----- Method: Linux64NewspeakSistaSpur>>interpreterClass (in category 'source generation') -----
+ interpreterClass
+ 	^ CoInterpreter
+ !

Item was added:
+ ----- Method: Linux64NewspeakSistaV3>>cogitClass (in category 'source generation') -----
+ cogitClass
+ 	^SistaStackToRegisterMappingCogit
+ !

Item was removed:
- ----- Method: Linux64NewspeakSistaV3>>dirBuildPlatform (in category 'cmake') -----
- dirBuildPlatform
- 	"the directory for the platform. example: build.linux32x86"
- 	^self dirLinux32x8664!

Item was added:
+ ----- Method: Linux64NewspeakSistaV3>>interpreterClass (in category 'source generation') -----
+ interpreterClass
+ 	^ CoInterpreter
+ !

Item was added:
+ ----- Method: Linux64NewspeakStackSpur>>cogitClass (in category 'source generation') -----
+ cogitClass
+ 	^ StackToRegisterMappingCogit 
+ !

Item was removed:
- ----- Method: Linux64NewspeakStackSpur>>dirBuildPlatform (in category 'cmake') -----
- dirBuildPlatform
- 	"the directory for the platform. example: build.linux32x86"
- 	^self dirLinux32x8664!

Item was added:
+ ----- Method: Linux64NewspeakStackSpur>>interpreterClass (in category 'source generation') -----
+ interpreterClass
+ 	^ StackInterpreter!

Item was added:
+ ----- Method: Linux64NewspeakStackV3>>cogitClass (in category 'source generation') -----
+ cogitClass
+ 	^ StackToRegisterMappingCogit 
+ !

Item was removed:
- ----- Method: Linux64NewspeakStackV3>>dirBuildPlatform (in category 'cmake') -----
- dirBuildPlatform
- 	"the directory for the platform. example: build.linux32x86"
- 	^self dirLinux32x8664!

Item was added:
+ ----- Method: Linux64NewspeakStackV3>>interpreterClass (in category 'source generation') -----
+ interpreterClass
+ 	^ StackInterpreter!

Item was added:
+ ----- Method: Linux64SqueakCogSpur>>cogitClass (in category 'source generation') -----
+ cogitClass
+ 	^ StackToRegisterMappingCogit 
+ !

Item was removed:
- ----- Method: Linux64SqueakCogSpur>>dirBuildPlatform (in category 'cmake') -----
- dirBuildPlatform
- 	"the directory for the platform. example: build.linux32x86"
- 	^self dirLinux32x8664!

Item was added:
+ ----- Method: Linux64SqueakCogSpur>>interpreterClass (in category 'source generation') -----
+ interpreterClass
+ 	^ CoInterpreter
+ !

Item was added:
+ ----- Method: Linux64SqueakCogV3>>cogitClass (in category 'source generation') -----
+ cogitClass
+ 	^ StackToRegisterMappingCogit 
+ !

Item was removed:
- ----- Method: Linux64SqueakCogV3>>dirBuildPlatform (in category 'cmake') -----
- dirBuildPlatform
- 	"the directory for the platform. example: build.linux32x86"
- 	^self dirLinux32x8664!

Item was added:
+ ----- Method: Linux64SqueakCogV3>>interpreterClass (in category 'source generation') -----
+ interpreterClass
+ 	^ CoInterpreter
+ !

Item was added:
+ ----- Method: Linux64SqueakSistaSpur>>cogitClass (in category 'source generation') -----
+ cogitClass
+ 	^SistaStackToRegisterMappingCogit
+ !

Item was removed:
- ----- Method: Linux64SqueakSistaSpur>>dirBuildPlatform (in category 'as yet unclassified') -----
- dirBuildPlatform
- 	"the directory for the platform. example: build.linux32x86"
- 	^self dirLinux32x8664!

Item was added:
+ ----- Method: Linux64SqueakSistaSpur>>interpreterClass (in category 'source generation') -----
+ interpreterClass
+ 	^ CoInterpreter
+ !

Item was added:
+ ----- Method: Linux64SqueakSistaV3>>cogitClass (in category 'source generation') -----
+ cogitClass
+ 	^SistaStackToRegisterMappingCogit
+ !

Item was removed:
- ----- Method: Linux64SqueakSistaV3>>dirBuildPlatform (in category 'cmake') -----
- dirBuildPlatform
- 	"the directory for the platform. example: build.linux32x86"
- 	^self dirLinux32x8664!

Item was added:
+ ----- Method: Linux64SqueakSistaV3>>interpreterClass (in category 'source generation') -----
+ interpreterClass
+ 	^ CoInterpreter
+ !

Item was added:
+ ----- Method: Linux64SqueakStackSpur>>cogitClass (in category 'source generation') -----
+ cogitClass
+ 	^ StackToRegisterMappingCogit 
+ !

Item was removed:
- ----- Method: Linux64SqueakStackSpur>>dirBuildPlatform (in category 'cmake') -----
- dirBuildPlatform
- 	"the directory for the platform. example: build.linux32x86"
- 	^self dirLinux32x8664!

Item was added:
+ ----- Method: Linux64SqueakStackSpur>>interpreterClass (in category 'source generation') -----
+ interpreterClass
+ 	^ StackInterpreter!

Item was added:
+ ----- Method: Linux64SqueakStackV3>>cogitClass (in category 'source generation') -----
+ cogitClass
+ 	^ StackToRegisterMappingCogit 
+ !

Item was removed:
- ----- Method: Linux64SqueakStackV3>>dirBuildPlatform (in category 'cmake') -----
- dirBuildPlatform
- 	"the directory for the platform. example: build.linux32x86"
- 	^self dirLinux32x8664!

Item was added:
+ ----- Method: Linux64SqueakStackV3>>interpreterClass (in category 'source generation') -----
+ interpreterClass
+ 	^ StackInterpreter!

Item was changed:
+ SqueakUnixConfig subclass: #Linux64x86w32BitConfig
+ 	instanceVariableNames: ''
- CogFamilyUnixConfig subclass: #Linux64x86w32BitConfig
- 	instanceVariableNames: 'buildType generateBuild generateBuildAssert generateBuildAssertITimerHeartbeat generateBuildDebug generateBuildDebugITimerHeartbeat generateBuildDebugMultiThreaded generateBuildIHeartbeatTimer generateBuildMultiThreaded generateBuildMultiThreadedAssert generateBuildMultiThreadedDebug'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'CMakeVMMakerSqueak-Linux64X86-32BitCompatibility'!
  
  !Linux64x86w32BitConfig commentStamp: 'tty 6/15/2014 13:49' prior: 0!
  I provide base class functionality.
  
  I am not meant to be built.
  
  SqueakLinux64x86w32CompatBuilder 
  	configureABuildFor: #ONE OF MY SUBCLASSES NAME HERE withBuildType: #build;
  	generateSources;
  	generate.  
  
  HelpBrowser openOn: CMakeVMMakerSqueakEndUserHelp
  HelpBrowser openOn: CMakeVMMakerSqueakDeveloperHelp
  
  
  !

Item was removed:
- ----- Method: Linux64x86w32BitConfig>>addDriver:sources:generator:externalLibs: (in category 'squeak compatibility') -----
- addDriver: name sources: aSources generator: cmakeGen externalLibs: extLibs
- 
- 	| cfg srcs |
- 	
- 	srcs := aSources inject: '' into: [:res :each | res , ' "', each, '"' ].
- 	cfg := cmakeGen
- 		captureOutputDuring: [
- 			cmakeGen printHeader;
- 			project: name;
- 			include: '../directories.cmake';
- 		
- 			message: 'Adding module: ', name;
- 			
- 			addDefinitions:  self compilerFlags;
- 			addDefinitions: '-fPIC -DPIC';
- 			set: #sources to: srcs;
- 			cmd: 'add_library' params: name, ' SHARED ${sources}'; 
- 			includeDirectories: '${crossDir}/plugins/FilePlugin';
- 			includeDirectories: '${targetPlatform}/plugins/B3DAcceleratorPlugin';
- 			includeDirectories: '${crossDir}/plugins/B3DAcceleratorPlugin';
- 			set: 'LIBRARY_OUTPUT_PATH' toString: self outputDir fullName;
- 			addExternalLibraries: extLibs;
- 			cmd: 'target_link_libraries' params: name , ' ${LINKLIBS}';
- 			cmd: 'set_target_properties' params: name , ' PROPERTIES PREFIX "" SUFFIX "" 
- 			LINK_FLAGS -m32' 
- 	].
- 	
- 	(self buildDir / name) assureExistence.
- 	self write: cfg toFile: name , '/', cmakeGen outputFileName.
- 	cmakeGen addSubdirectory:  name.
- 	!

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

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

Item was removed:
- ----- Method: Linux64x86w32BitConfig>>buildScript (in category 'squeak compatibility') -----
- buildScript
- 	"answer the build script for building everything"
- 	
- 
- 	^ 
- '#!!/usr/bin/env bash
- 
- cmake .
- make
- 
- '!

Item was removed:
- ----- Method: Linux64x86w32BitConfig>>buildType: (in category 'squeak compatibility') -----
- buildType: aSymbol
- 	buildType:= aSymbol!

Item was removed:
- ----- Method: Linux64x86w32BitConfig>>cogitClass (in category 'source generation') -----
- cogitClass
- 	^ StackToRegisterMappingCogit !

Item was removed:
- ----- Method: Linux64x86w32BitConfig>>configH (in category 'squeak compatibility') -----
- configH
- 	" right now its like  that "
- 	^ '
- #ifndef __sq_config_h
- #define __sq_config_h
- 
- /* explicit image width */
- 
- #define HAVE_INTERP_H 1
- 
- /* package options */
- 
- #define USE_X11 1
- #define USE_X11_GLX 1
- /* #undef       USE_QUARTZ */
- /* #undef       USE_QUARTZ_CGL */
- /* #undef       USE_RFB */
- 
- /* libraries */
- 
- /* #undef       HAVE_LIBX11 */
- #define HAVE_LIBXEXT 1
- #define HAVE_LIBDL 1
- /* #undef       HAVE_DYLD */
- /* #undef       HAVE_LIBFFI */
- /* #undef       HAVE_ICONV */
- 
- /* #undef       USE_AUDIO_NONE */
- /* #undef       USE_AUDIO_SUN */
- /* #undef       USE_AUDIO_NAS */
- /* #undef       USE_AUDIO_OSS */
- /* #undef       USE_AUDIO_MACOSX */
- /* #undef       OSS_DEVICE */
- 
- /* header files */
- 
- #define HAVE_UNISTD_H 1
- /* #undef       NEED_GETHOSTNAME_P */
- 
- #define HAVE_DIRENT_H 1
- /* #undef       HAVE_SYS_NDIR_H */
- /* #undef       HAVE_SYS_DIR_H */
- /* #undef       HAVE_NDIR_H */
- #define HAVE_DLFCN_H 1
- /* #undef       HAVE_ICONV_H */
- 
- #define HAVE_SYS_TIME_H 1
- #define TIME_WITH_SYS_TIME 1
- 
- #define HAVE_SYS_FILIO_H 1
- 
- /* #undef       HAVE_SYS_AUDIOIO_H */
- /* #undef       HAVE_SUN_AUDIOIO_H */
- 
- /* #undef       HAVE_PTY_H */
- /* #undef       HAVE_UTIL_H */
- #define HAVE_LIBUTIL_H 1
- /* #undef       HAVE_STROPTS_H */
- 
- #define HAVE_GL_GL_H 1
- /* #undef       HAVE_OPENGL_GL_H */
- 
- /* #undef       NEED_SUNOS_H */
- 
- 
- #define HAVE_UUID_H
- /* system calls/library functions */
- 
- #define AT_EXIT atexit
- 
- #define HAVE_TZSET 1
- 
- #define HAVE_OPENPTY 1
- /* #undef       HAVE_UNIX98_PTYS */
- 
- #define HAVE_SNPRINTF 1
- /* #undef       HAVE___SNPRINTF */
- 
- #define HAVE_MMAP 1
- 
- /* #undef       HAVE_DYLD */
- 
- #define HAVE_LANGINFO_CODESET 1
- 
- #define HAVE_ALLOCA 1
- /* #undef       HAVE_ALLOCA_H */
- 
- #define HAVE_UNSETENV 1
- 
- #define HAVE_NANOSLEEP 1
- 
- /* widths of primitive types */
- 
- #define SIZEOF_INT 4
- #define SIZEOF_LONG 4
- #define SIZEOF_LONG_LONG 8
- #define SIZEOF_VOID_P 4
- 
- /* structures */
- 
- #define HAVE_TM_GMTOFF 1
- #define HAVE_TIMEZONE 1
- 
- /* typedefs */
- 
- /* #undef       size_t */
- /* #undef       socklen_t */
- 
- #define squeakInt64 long long
- 
- /* architecture */
- 
- #define OS_TYPE "unix"
- 
- #define VM_HOST "i386-freebsd8.2"
- #define VM_HOST_CPU "i386"
- /* #undef       VM_HOST_VENDOR */
- #define VM_HOST_OS "freebsd8.2"
- #define VM_BUILD_STRING "Unix built on "__DATE__ " "__TIME__" Compiler: "__VERSION__
- 
- /* #undef       WORDS_BIGENDIAN */
- /* #undef       DOUBLE_WORD_ALIGNMENT */
- 
- /* damage containment */
- 
- /* #undef       DARWIN */
- 
- #ifdef NEED_SUNOS_H
- # include "sunos.h"
- #endif
- 
- /* other configured variables */
- 
- #define SQ_VERSION "3.9a-7024"
- #define VM_VERSION "3.9-7"
- #define VM_MODULE_PREFIX ""
- /* #undef VM_DLSYM_PREFIX */
- #define VM_X11DIR "/usr/X11R6/lib"
- 
- /* avoid dependencies on glibc2.3 */
- 
- /* #undef HAVE_FEATURES_H */
- 
- #if defined(HAVE_FEATURES_H)
- # include "glibc.h"
- #endif
- 
- #endif /* __sq_config_h */
- 																																																																					
- 																																																																				'!

Item was changed:
  ----- Method: Linux64x86w32BitConfig>>configureForBuildType: (in category 'cmake') -----
  configureForBuildType: aSymbol
  	| d |
  	"provide a concrete builder with the buildType and configureBuildX method to invoke"
  	d:= SqueakCMakeVMMakerAbstractBuilder default buildTypeAndDirectoryInfo copy.
  	self configureNoBuildType.                "reset all internal flags"
  	d 
  		at: #build 
  		put: [self buildType:#build.  self configureBuild];
  
  		at: #buildAssert 
  		put: [self buildType: #buildAssert.  	self configureBuildAssert];
  
  		at: #buildAssertITimerHeartbeat 
  		put:     [ self buildType: #buildAssertITimerHeartbeat.   self configureBuildAssertITimerHeartbeat];
  
              at:#buildDebug 
  		put: [self buildType: #buildDebug.  self configureBuildDebug];
  
  		at: #buildDebugITimerHeartbeat 
  		put:  [self buildType: #buildDebugITimerHeartbeat.   self configureBuildDebugITimerHeartbeat];
  
  		at: #buildITimerHeartbeat 
  		put: [self buildType:#buildITimerHeartbeat.    self configureBuildIHeartbeatTimer];
  
  		at: #buildMultiThreaded 
  		put:  [self buildType:#buildMultiThreaded . self configureBuildMultiThreaded];
  
  		at: #buildMultiThreadedAssert 
  		put: [self buildType: #buildMultiThreadedAssert. self configureBuildMultiThreadedAssert];
  
  		at: #buildMultiThreadedDebug  
  		put: [self buildType: #buildMultiThreadedDebug. self configureBuildMultiThreadedDebug].
- 
       ^(d at: aSymbol).!

Item was removed:
- ----- Method: Linux64x86w32BitConfig>>dirFrom: (in category 'squeak compatibility') -----
- dirFrom: aStringOrDir
- 	^ aStringOrDir isString
- 		ifTrue: [ FileDirectory forFileName: aStringOrDir  ]
- 		ifFalse: [ aStringOrDir ]!

Item was changed:
  ----- Method: Linux64x86w32BitConfig>>executableName (in category 'accessing') -----
  executableName
+ 	self subclassResponsibility!
- 	self required!

Item was removed:
- ----- Method: Linux64x86w32BitConfig>>executableType (in category 'accessing') -----
- executableType
- 	^''
- 
- "
- SystemNavigation default browseMethodsWhoseNamesContain: ''executableType''
- 	^ 'MACOSX_BUNDLE'
- 	^ 'WIN32'\
- 	^ ''
- "!

Item was removed:
- ----- Method: Linux64x86w32BitConfig>>frameworks (in category 'accessing') -----
- frameworks
- 	"leave empty for all platforms but Mac OS"
- 	^ #()!

Item was removed:
- ----- Method: Linux64x86w32BitConfig>>generate (in category 'squeak compatibility') -----
- generate
- 	self generatePluginsList. 
- 	self generateLicense. 
- 	^ CMakeVMGeneratorForSqueak generate: self !

Item was removed:
- ----- Method: Linux64x86w32BitConfig>>generateLicense (in category 'accessing') -----
- generateLicense 
- 	self 
- 		write:  (self class licenseTemplate 
- 			format: { self version })
- 		toFile: 'LICENSE.txt'
- 	!

Item was removed:
- ----- Method: Linux64x86w32BitConfig>>generatePluginsList (in category 'accessing') -----
- generatePluginsList 
- 	self 
- 		write:  (self class pluginsTemplate 
- 			format: {
- 				self version. 
- 				String streamContents: [ :stream | self internalPlugins asStringOn: stream delimiter: String cr ].
- 				String streamContents: [ :stream | self externalPlugins asStringOn: stream delimiter: String cr ].
- 				self executableName })
- 		toFile: 'PLUGINS.txt'
- 	!

Item was removed:
- ----- Method: Linux64x86w32BitConfig>>interpreterClass (in category 'source generation') -----
- interpreterClass
- 	self required.
- 	"
- 	^ CoInterpreter
- 	^ CoInterpreterMT
- 	^ StackInterpreter
- 	^ StackEvtAndroidInterpreter
- 	??other
- 	"!

Item was removed:
- ----- Method: Linux64x86w32BitConfig>>outputDir (in category 'squeak compatibility') -----
- outputDir
- 
- 	"the directory where built binaries will be stored"
- 	^ outputDir ifNil: [ outputDir := (self topDir / self dirOutput /  self dirInstall) ]	
- 
- !

Item was removed:
- ----- Method: Linux64x86w32BitConfig>>prepareForGeneration (in category 'source generation') -----
- prepareForGeneration
- 	self required
- 
- 	"^self prepareForCogGeneration
- 	  ^self prepareForStackVMGeneration
- 		
- 	  CPlatformConfig browse"
- !

Item was removed:
- ----- Method: Linux64x86w32BitConfig>>prepareVMMaker (in category 'squeak compatibility') -----
- 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 removed:
- ----- Method: Linux64x86w32BitConfig>>setupDirectories: (in category 'squeak compatibility') -----
- setupDirectories: aMaker
- 	| dirsInclude |
- 
- 	" write the directories in separate include file"
- 	dirsInclude := aMaker captureOutputDuring: [
- 		aMaker
- 			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'.
- 	
- 	aMaker include: 'directories.cmake'.
- !

Item was removed:
- ----- Method: Linux64x86w32BitConfig>>srcDir (in category 'squeak compatibility') -----
- srcDir
- 		^ srcDir ifNil: [ srcDir := (self topDir directoryNamed: 'src' )]!

Item was removed:
- ----- Method: Linux64x86w32BitConfig>>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 removed:
- ----- Method: Linux64x86w32BitConfig>>validateSourcesPresent (in category 'squeak compatibility') -----
- validateSourcesPresent
- 	| sources |
- 	sources := Smalltalk sourcesName.
- 	
- 	(sources == nil)
- 		ifTrue: [	self error: 'VM source code cannot be generated without .sources file'.]		!

Item was removed:
- ----- Method: Linux64x86w32BitConfig>>version (in category 'accessing') -----
- version
- 	^ ''!

Item was removed:
- ----- Method: Linux64x86w32BitConfig>>write:toFile: (in category 'squeak compatibility') -----
- 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 added:
+ ----- Method: Linux64x86w32BitSqueakCogV3SlackwareNoGLConfig>>cogitClass (in category 'source generation') -----
+ cogitClass
+ 	^ StackToRegisterMappingCogit 
+ !

Item was removed:
- ----- Method: Linux64x86w32BitSqueakCogV3SlackwareNoGLConfig>>prepareForGeneration (in category 'source generation') -----
- prepareForGeneration
- 	^self prepareForCogGeneration
- !

Item was removed:
- ----- Method: Linux64x86w32BitSqueakCogV3SlackwareNoGLConfig>>setupDirectories: (in category 'squeak compatibility') -----
- setupDirectories: gen
- 	super setupDirectories: gen.
- 	gen set: #externalModulesDir toString: self externalModulesDir.!

Item was added:
+ ----- Method: MacOSX32x86NewspeakCogSpur>>cogitClass (in category 'source generation') -----
+ cogitClass
+ 	^ StackToRegisterMappingCogit 
+ !

Item was added:
+ ----- Method: MacOSX32x86NewspeakCogSpur>>interpreterClass (in category 'source generation') -----
+ interpreterClass
+ 	^ CoInterpreter
+ !

Item was added:
+ ----- Method: MacOSX32x86NewspeakCogV3>>cogitClass (in category 'source generation') -----
+ cogitClass
+ 	^ StackToRegisterMappingCogit 
+ !

Item was added:
+ ----- Method: MacOSX32x86NewspeakCogV3>>interpreterClass (in category 'source generation') -----
+ interpreterClass
+ 	^ CoInterpreter
+ !

Item was added:
+ ----- Method: MacOSX32x86NewspeakSistaSpur>>cogitClass (in category 'source generation') -----
+ cogitClass
+ 	^SistaStackToRegisterMappingCogit
+ !

Item was added:
+ ----- Method: MacOSX32x86NewspeakSistaSpur>>interpreterClass (in category 'source generation') -----
+ interpreterClass
+ 	^ CoInterpreter
+ !

Item was added:
+ ----- Method: MacOSX32x86NewspeakSistaV3>>cogitClass (in category 'source generation') -----
+ cogitClass
+ 	^SistaStackToRegisterMappingCogit
+ !

Item was added:
+ ----- Method: MacOSX32x86NewspeakSistaV3>>interpreterClass (in category 'source generation') -----
+ interpreterClass
+ 	^ CoInterpreter
+ !

Item was added:
+ ----- Method: MacOSX32x86NewspeakStackSpur>>cogitClass (in category 'source generation') -----
+ cogitClass
+ 	^ StackToRegisterMappingCogit 
+ !

Item was added:
+ ----- Method: MacOSX32x86NewspeakStackSpur>>interpreterClass (in category 'source generation') -----
+ interpreterClass
+ 	^ StackInterpreter!

Item was added:
+ ----- Method: MacOSX32x86NewspeakStackV3>>cogitClass (in category 'source generation') -----
+ cogitClass
+ 	^ StackToRegisterMappingCogit 
+ !

Item was added:
+ ----- Method: MacOSX32x86NewspeakStackV3>>interpreterClass (in category 'source generation') -----
+ interpreterClass
+ 	^ StackInterpreter!

Item was added:
+ ----- Method: MacOSX32x86SqueakCogSpur>>cogitClass (in category 'source generation') -----
+ cogitClass
+ 	^ StackToRegisterMappingCogit 
+ !

Item was added:
+ ----- Method: MacOSX32x86SqueakCogSpur>>interpreterClass (in category 'source generation') -----
+ interpreterClass
+ 	^ CoInterpreter
+ !

Item was added:
+ ----- Method: MacOSX32x86SqueakCogV3>>cogitClass (in category 'source generation') -----
+ cogitClass
+ 	^ StackToRegisterMappingCogit 
+ !

Item was added:
+ ----- Method: MacOSX32x86SqueakCogV3>>interpreterClass (in category 'source generation') -----
+ interpreterClass
+ 	^ CoInterpreter
+ !

Item was added:
+ ----- Method: MacOSX32x86SqueakSistaSpur>>cogitClass (in category 'source generation') -----
+ cogitClass
+ 	^SistaStackToRegisterMappingCogit
+ !

Item was added:
+ ----- Method: MacOSX32x86SqueakSistaSpur>>interpreterClass (in category 'source generation') -----
+ interpreterClass
+ 	^ CoInterpreter
+ !

Item was added:
+ ----- Method: MacOSX32x86SqueakSistaV3>>cogitClass (in category 'source generation') -----
+ cogitClass
+ 	^SistaStackToRegisterMappingCogit
+ !

Item was added:
+ ----- Method: MacOSX32x86SqueakSistaV3>>interpreterClass (in category 'source generation') -----
+ interpreterClass
+ 	^ CoInterpreter
+ !

Item was added:
+ ----- Method: MacOSX32x86SqueakStackSpur>>cogitClass (in category 'source generation') -----
+ cogitClass
+ 	^ StackToRegisterMappingCogit 
+ !

Item was added:
+ ----- Method: MacOSX32x86SqueakStackSpur>>interpreterClass (in category 'source generation') -----
+ interpreterClass
+ 	^ StackInterpreter!

Item was added:
+ ----- Method: MacOSX32x86SqueakStackV3>>cogitClass (in category 'source generation') -----
+ cogitClass
+ 	^ StackToRegisterMappingCogit 
+ !

Item was added:
+ ----- Method: MacOSX32x86SqueakStackV3>>interpreterClass (in category 'source generation') -----
+ interpreterClass
+ 	^ StackInterpreter!

Item was changed:
+ SqueakUnixConfig subclass: #SqueakAndroidStackEvtConfig
+ 	instanceVariableNames: ''
- CPlatformConfigForSqueak subclass: #SqueakAndroidStackEvtConfig
- 	instanceVariableNames: 'buildType generateBuild generateBuildAssert generateBuildAssertITimerHeartbeat generateBuildDebug generateBuildDebugITimerHeartbeat generateBuildDebugMultiThreaded generateBuildIHeartbeatTimer generateBuildMultiThreaded generateBuildMultiThreadedAssert generateBuildMultiThreadedDebug'
  	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. !

Item was removed:
- ----- Method: SqueakAndroidStackEvtConfig>>buildDir (in category 'directories') -----
- buildDir
- 	^ buildDir ifNil: [ buildDir := ( self topDir / self buildDirName) assureExistence].!

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

Item was added:
+ ----- Method: SqueakAndroidStackEvtConfig>>cogitClass (in category 'source generation') -----
+ cogitClass
+ 	^ StackToRegisterMappingCogit 
+ !

Item was removed:
- ----- Method: SqueakAndroidStackEvtConfig>>fixLineEndsOf: (in category 'utils') -----
- fixLineEndsOf: string
- 	^ string copyReplaceAll: String cr with: String lf!

Item was changed:
  ----- Method: SqueakAndroidStackEvtConfig>>interpreterClass (in category 'source generation') -----
  interpreterClass
+ "Does not exist in squeak"
+ "	^ StackEvtAndroidInterpreter"!
- 	^ StackEvtAndroidInterpreter!

Item was removed:
- ----- Method: SqueakAndroidStackEvtConfig>>outputDir (in category 'directories') -----
- outputDir
- 
- 	"the directory where built binaries will be stored"
- 	^ outputDir ifNil: [ outputDir := (self topDir / self dirOutput/ self dirInstall) ]	
- 
- !

Item was removed:
- ----- Method: SqueakAndroidStackEvtConfig>>setGlobalOptionsAfterDetermineSystem:buildType: (in category 'utils') -----
- setGlobalOptionsAfterDetermineSystem: aMaker buildType: aBuildType
- 	"invoke correct setGlobalOptions for this buildType to allow per-buildType customization'"
- 
- 	|d |
- 	d:= SqueakCMakeVMMakerAbstractBuilder default buildTypeAndDirectoryInfo copy.
- 	d 
- 		at: #build put: [self setGlobalOptionsAfterDetermineSystemBuild: aMaker];
- 		at: #buildAssert  put: [self setGlobalOptionsAfterDetermineSystemBuildAssert: aMaker];
- 		at: #buildAssertITimerHeartbeat  put: [self setGlobalOptionsAfterDetermineSystemBuildAssertITimerHeartbeat: aMaker];
-             at:#buildDebug  put: [self setGlobalOptionsAfterDetermineSystemBuildDebug: aMaker];   
- 		at: #buildITimerHeartbeat  put: [self setGlobalOptionsAfterDetermineSystemBuildITimerHeartbeat: aMaker];
- 		at: #buildMultiThreaded  put: [self setGlobalOptionsAfterDetermineSystemBuildMultiThreaded: aMaker ];
- 		at: #buildMultiThreadedAssert  put: [self setGlobalOptionsAfterDetermineSystemBuildMultiThreadedAssert: aMaker];
- 		at: #buildMultiThreadedDebug   put: [self setGlobalOptionsAfterDetermineSystemBuildMultiThreadedDebug: aMaker ];
- 		at: #buildNone put:[self setGlobalOptionsBuildNone: aMaker].
- 
- 	 ^(d at: ( aBuildType)) value
- !

Item was removed:
- ----- Method: SqueakAndroidStackEvtConfig>>setupDirectories: (in category 'directories') -----
- setupDirectories: gen
- 	"same logic as the super has, but use gmake syntax instead of cmake"
- 	| dirsInclude |
- 
- 	" write the directories in separate include file"
- 	dirsInclude := gen captureOutputDuring: [
- 		gen
- 			set: #topDir to: ('$(ROOT)/', self topDir fullName); 
- 			set: #buildDir to: (self buildDir ifNil: ['$(topDir)/build'] ifNotNil: ['$(ROOT)/', self buildDir fullName] );
- 			set: #platformsDir to: ('$(ROOT)/', self platformsDir);
- 			set: #srcDir to: ('$(ROOT)/', self srcDir);
- 			set: #srcPluginsDir to: (pluginsDir ifNil: [ '$(srcDir)/plugins' ]);
- 			set: #srcVMDir to: '$(srcDir)/vm';
- 			set: #platformName to: self platformName;
- 			set: #targetPlatform to: '$(platformsDir)/$(platformName)';
- 			set: #crossDir to: '$(platformsDir)/Cross';
- 			set: #platformVMDir to: '$(targetPlatform)/vm'.
- 	].
- 
- 	self write: dirsInclude toFile: 'cogdirs.mk'
- !

Item was removed:
- ----- Method: SqueakAndroidStackEvtConfig>>srcDir (in category 'directories') -----
- srcDir
- 		^ srcDir ifNil: [ srcDir := (self topDir directoryNamed: 'stacksrc' )]!

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

Item was changed:
+ SqueakUnixConfig subclass: #SqueakBSDConfig
+ 	instanceVariableNames: ''
- CogFamilyUnixConfig subclass: #SqueakBSDConfig
- 	instanceVariableNames: 'buildType generateBuild generateBuildAssert generateBuildAssertITimerHeartbeat generateBuildDebug generateBuildDebugITimerHeartbeat generateBuildDebugMultiThreaded generateBuildIHeartbeatTimer generateBuildMultiThreaded generateBuildMultiThreadedAssert generateBuildMultiThreadedDebug'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'CMakeVMMakerSqueak-BSD32x86'!
  
  !SqueakBSDConfig commentStamp: 'tty 6/15/2014 14:12' prior: 0!
  I configure a VM according to my name's form: [Operating System] [WordSize] [Processor Language][VM MemoryManager][BuildType]Conf
  
  I am not meant to be built.
  
  SqueakBSDx86Builder 
  	configureABuildFor: #MY SUBCLASS NAME HERE withBuildType: #build;
  	generateSources;
  	generate.  
  
  HelpBrowser openOn: CMakeVMMakerSqueakEndUserHelp
  HelpBrowser openOn: CMakeVMMakerSqueakDeveloperHelp
  
  !

Item was removed:
- ----- Method: SqueakBSDConfig>>addDriver:sources:generator:externalLibs: (in category 'accessing') -----
- addDriver: name sources: aSources generator: cmakeGen externalLibs: extLibs
- 
- 	| cfg srcs |
- 	
- 	srcs := aSources inject: '' into: [:res :each | res , ' "', each, '"' ].
- 	cfg := cmakeGen
- 		captureOutputDuring: [
- 			cmakeGen printHeader;
- 			project: name;
- 			include: '../directories.cmake';
- 		
- 			message: 'Adding module: ', name;
- 			
- 			addDefinitions:  self compilerFlags;
- 			addDefinitions: '-fPIC -DPIC';
- 			set: #sources to: srcs;
- 			cmd: 'add_library' params: name, ' SHARED ${sources}'; 
- 			includeDirectories: '${crossDir}/plugins/FilePlugin';
- 			includeDirectories: '${targetPlatform}/plugins/B3DAcceleratorPlugin';
- 			includeDirectories: '${crossDir}/plugins/B3DAcceleratorPlugin';
- 			set: 'LIBRARY_OUTPUT_PATH' toString: self outputDir fullName;
- 			addExternalLibraries: extLibs;
- 			cmd: 'target_link_libraries' params: name , ' ${LINKLIBS}';
- 			cmd: 'set_target_properties' params: name , ' PROPERTIES PREFIX "" SUFFIX "" 
- 			LINK_FLAGS -m32' 
- 	].
- 	
- 	(self buildDir / name) assureExistence.
- 	self write: cfg toFile: name , '/', cmakeGen outputFileName.
- 	cmakeGen addSubdirectory:  name.
- 	!

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

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

Item was removed:
- ----- Method: SqueakBSDConfig>>compilerFlags (in category 'squeak compatibility') -----
- compilerFlags
- 	|d commonFlags flags|
- 	d:= SqueakCMakeVMMakerAbstractBuilder default buildTypeAndDirectoryInfo copy.
- 	d 
- 		at: #build put: [self compilerFlagsBuild];
- 		at: #buildAssert  put: [self compilerFlagsAssert];
- 		at: #buildAssertITimerHeartbeat  put: [self compilerFlagsAssertITimerHeartbeat];
-             at:#buildDebug  put: [self compilerFlagsDebug];   "located in CMakeVMMaker CPlatformConfig"
- 		at: #buildDebugITimerHeartbeat  put: [self compilerFlagsDebugITimerHeartbeat ];
- 		at: #buildITimerHeartbeat  put: [self compilerFlagsIHeartbeatTimer];
- 		at: #buildMultiThreaded  put: [self compilerFlagsMultiThreaded ];
- 		at: #buildMultiThreadedAssert  put: [self compilerFlagsMultiThreadedAssert];
- 		at: #buildMultiThreadedDebug   put: [self compilerFlagsMultiThreadedDebug ];
- 		at: #buildNone put:[self compilerFlagsNoBuildType].
- 
-     flags:= String streamContents: [ :stream |
- 	 (((d at:  buildType) value)  collect: #withBlanksTrimmed as: Set)
- 		asStringOn: stream 
- 		delimiter:' '].
- 
-     commonFlags:=String streamContents: [ :stream |
- 		((self commonCompilerFlags) collect: #withBlanksTrimmed as: Set)
- 			asStringOn: stream 
- 			delimiter: ' ' ].
- 	^ commonFlags, ' ' ,flags.!

Item was removed:
- ----- Method: SqueakBSDConfig>>dirFrom: (in category 'squeak compatibility') -----
- dirFrom: aStringOrDir
- 	^ aStringOrDir isString
- 		ifTrue: [ FileDirectory forFileName: aStringOrDir  ]
- 		ifFalse: [ aStringOrDir ]!

Item was removed:
- ----- Method: SqueakBSDConfig>>executableName (in category 'squeak compatibility') -----
- executableName
- 	^ 'cogvm'!

Item was removed:
- ----- Method: SqueakBSDConfig>>outputDir (in category 'squeak compatibility') -----
- outputDir
- 
- 	"the directory where built binaries will be stored"
- 	^ outputDir ifNil: [ outputDir := (self topDir / self dirOutput/ self dirInstall) ]	
- 
- !

Item was removed:
- ----- Method: SqueakBSDConfig>>prepareVMMaker (in category 'squeak compatibility') -----
- 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 removed:
- ----- Method: SqueakBSDConfig>>setupDirectories: (in category 'squeak compatibility') -----
- 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 removed:
- ----- Method: SqueakBSDConfig>>srcDir (in category 'squeak compatibility') -----
- srcDir
- 		^ srcDir ifNil: [ srcDir := (self topDir directoryNamed: 'src' )]!

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

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

Item was removed:
- ----- Method: SqueakBSDConfig>>write:toFile: (in category 'squeak compatibility') -----
- 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 added:
+ Object subclass: #SqueakCMakeSourceDistroBuilder
+ 	instanceVariableNames: 'buildTypeAndDirectoryInfo config'
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'CMakeVMMakerSqueak-Builder'!
+ 
+ !SqueakCMakeSourceDistroBuilder commentStamp: 'tty 6/18/2014 09:56' prior: 0!
+ A SqueakCMakeSourceDistroBuilder does nothing.
+ 
+ However, there is a need to create Source Packages for the Linux Package maintainers: Ubuntu, Slackware, SunOS, RedHat, Debain..etc
+ 
+ The CMakeVMMaker Design Pattern (essentially a Visitor pattern kicked off by Builders) would be spot on for this task.
+ 
+ I will address this when I am done with the VMGenerator.
+ 
+ tty. 2014.06.17!

Item was changed:
  ----- Method: SqueakCMakeVMMakerAbstractBuilder>>configureABuildFor:withBuildType: (in category 'building') -----
  configureABuildFor: configSymbol withBuildType: typeSymbol
  	| i |
  	self flag:'tty'. "excludeFromBuild returning True does not exit gracefully"
  	"Do some sanity checks, then set the internal state of a Configuration for a particular build type. "
  	[
  	((Smalltalk at: configSymbol)  category) =  (self configurationsCategory)  "verify the class is handled by this concrete builder"
  		ifTrue:[	
  				config := (Smalltalk at: configSymbol) new.                              "verify this config can handle this build type."
  				config excludeFromBuild                                                         "has a developer excluded this build manually?"
  					ifTrue:[^self userErrorConfigMarkedAsExcludeFromBuild: configSymbol].   
  				i:=config availableBuilds indexOf:typeSymbol                                    
  						ifAbsent:[^self userErrorInvalidBuildType: typeSymbol "this config does not support this build type"
  										forConfiguration: configSymbol 
  										hasTypes: config availableBuilds].
+ 
  				(config configureForBuildType: typeSymbol) value.                             "config configure yourself"
  				^self]
  		ifFalse:[^self userErrorInvalidTarget: configSymbol]
  	] ifError:[^'error configureABuildFor: ''', configSymbol].
  
  	^nil.
  	
  
  	!

Item was added:
+ ----- Method: SqueakCocoaIOSCogV3FamilyConfig>>cogitClass (in category 'source generation') -----
+ cogitClass
+ 	^ StackToRegisterMappingCogit 
+ !

Item was added:
+ ----- Method: SqueakCocoaIOSCogV3FamilyConfig>>interpreterClass (in category 'source generation') -----
+ interpreterClass
+ 	^ CoInterpreter
+ !

Item was added:
+ ----- Method: SqueakCocoaIOSCogV3MultiThreadedConfigz>>cogitClass (in category 'source generation') -----
+ cogitClass
+ 	^ StackToRegisterMappingCogit 
+ !

Item was changed:
  ----- Method: SqueakCocoaIOSCogV3MultiThreadedConfigz>>executableName (in category 'accessing') -----
  executableName
+ 	^ self vmCogExecutableName!
- 	^ 'CogMTVM'!

Item was removed:
- ----- Method: SqueakCocoaIOSConfig>>executableType (in category 'accessing') -----
- executableType
- 	^ 'MACOSX_BUNDLE'!

Item was removed:
- ----- Method: SqueakCocoaIOSConfig>>prepareVMMaker (in category 'source generation') -----
- 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 removed:
- ----- Method: SqueakCocoaIOSConfig>>write:toFile: (in category 'directories') -----
- 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 removed:
- ----- Method: SqueakCocoaIOSSqueakCogV3Config>>prepareForGeneration (in category 'source generation') -----
- prepareForGeneration
- 	^ self prepareForCogGeneration
- !

Item was removed:
- ----- Method: SqueakCocoaIOSSqueakStackV3Config>>prepareForGeneration (in category 'source generation') -----
- prepareForGeneration
- 	^ self prepareForStackVMGeneration
- !

Item was added:
+ ----- Method: SqueakFreeBSDNewspeakCogSpurConfig>>cogitClass (in category 'source generation') -----
+ cogitClass
+ 	^ StackToRegisterMappingCogit 
+ !

Item was added:
+ ----- Method: SqueakFreeBSDNewspeakCogSpurConfig>>interpreterClass (in category 'source generation') -----
+ interpreterClass
+ 	^ CoInterpreter
+ !

Item was added:
+ ----- Method: SqueakFreeBSDNewspeakCogV3Config>>cogitClass (in category 'source generation') -----
+ cogitClass
+ 	^ StackToRegisterMappingCogit 
+ !

Item was added:
+ ----- Method: SqueakFreeBSDNewspeakCogV3Config>>interpreterClass (in category 'source generation') -----
+ interpreterClass
+ 	^ CoInterpreter
+ !

Item was added:
+ ----- Method: SqueakFreeBSDNewspeakSistaSpurConfig>>cogitClass (in category 'source generation') -----
+ cogitClass
+ 	^SistaStackToRegisterMappingCogit
+ !

Item was added:
+ ----- Method: SqueakFreeBSDNewspeakSistaSpurConfig>>interpreterClass (in category 'source generation') -----
+ interpreterClass
+ 	^ CoInterpreter
+ !

Item was added:
+ ----- Method: SqueakFreeBSDNewspeakSistaV3Config>>cogitClass (in category 'source generation') -----
+ cogitClass
+ 	^SistaStackToRegisterMappingCogit
+ !

Item was added:
+ ----- Method: SqueakFreeBSDNewspeakSistaV3Config>>interpreterClass (in category 'source generation') -----
+ interpreterClass
+ 	^ CoInterpreter
+ !

Item was added:
+ ----- Method: SqueakFreeBSDNewspeakStackSpurConfig>>cogitClass (in category 'source generation') -----
+ cogitClass
+ 	^ StackToRegisterMappingCogit 
+ !

Item was added:
+ ----- Method: SqueakFreeBSDNewspeakStackSpurConfig>>interpreterClass (in category 'source generation') -----
+ interpreterClass
+ 	^ StackInterpreter!

Item was added:
+ ----- Method: SqueakFreeBSDNewspeakStackV3Config>>cogitClass (in category 'source generation') -----
+ cogitClass
+ 	^ StackToRegisterMappingCogit 
+ !

Item was added:
+ ----- Method: SqueakFreeBSDNewspeakStackV3Config>>interpreterClass (in category 'source generation') -----
+ interpreterClass
+ 	^ StackInterpreter!

Item was added:
+ ----- Method: SqueakFreeBSDSqueakCogSpurConfig>>cogitClass (in category 'source generation') -----
+ cogitClass
+ 	^ StackToRegisterMappingCogit 
+ !

Item was added:
+ ----- Method: SqueakFreeBSDSqueakCogSpurConfig>>interpreterClass (in category 'source generation') -----
+ interpreterClass
+ 	^ CoInterpreter
+ !

Item was added:
+ ----- Method: SqueakFreeBSDSqueakCogV3Config>>cogitClass (in category 'source generation') -----
+ cogitClass
+ 	^ StackToRegisterMappingCogit 
+ !

Item was added:
+ ----- Method: SqueakFreeBSDSqueakCogV3Config>>interpreterClass (in category 'source generation') -----
+ interpreterClass
+ 	^ CoInterpreter
+ !

Item was added:
+ ----- Method: SqueakFreeBSDSqueakSistaSpurConfig>>cogitClass (in category 'source generation') -----
+ cogitClass
+ 	^SistaStackToRegisterMappingCogit
+ !

Item was added:
+ ----- Method: SqueakFreeBSDSqueakSistaSpurConfig>>interpreterClass (in category 'source generation') -----
+ interpreterClass
+ 	^ CoInterpreter
+ !

Item was added:
+ ----- Method: SqueakFreeBSDSqueakSistaV3Config>>cogitClass (in category 'source generation') -----
+ cogitClass
+ 	^SistaStackToRegisterMappingCogit
+ !

Item was added:
+ ----- Method: SqueakFreeBSDSqueakSistaV3Config>>interpreterClass (in category 'source generation') -----
+ interpreterClass
+ 	^ CoInterpreter
+ !

Item was added:
+ ----- Method: SqueakFreeBSDSqueakStackSpurConfig>>cogitClass (in category 'source generation') -----
+ cogitClass
+ 	^ StackToRegisterMappingCogit 
+ !

Item was added:
+ ----- Method: SqueakFreeBSDSqueakStackSpurConfig>>interpreterClass (in category 'source generation') -----
+ interpreterClass
+ 	^ StackInterpreter!

Item was added:
+ ----- Method: SqueakFreeBSDSqueakStackV3Config>>cogitClass (in category 'source generation') -----
+ cogitClass
+ 	^ StackToRegisterMappingCogit 
+ !

Item was added:
+ ----- Method: SqueakFreeBSDSqueakStackV3Config>>interpreterClass (in category 'source generation') -----
+ interpreterClass
+ 	^ StackInterpreter!

Item was changed:
  CPlatformConfigForSqueak subclass: #SqueakIA32BochsConfig
+ 	instanceVariableNames: ''
- 	instanceVariableNames: 'buildType generateBuild generateBuildAssert generateBuildAssertITimerHeartbeat generateBuildDebug generateBuildDebugITimerHeartbeat generateBuildDebugMultiThreaded generateBuildIHeartbeatTimer generateBuildMultiThreaded generateBuildMultiThreadedAssert generateBuildMultiThreadedDebug'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'CMakeVMMakerSqueak-IA32-Bochs'!
  
  !SqueakIA32BochsConfig commentStamp: 'tty 6/15/2014 14:08' prior: 0!
  N.B. I honestly have no idea how to use this. tty (:
  
  I configure a VM according to my name's form: [Operating System] [WordSize] [Processor Language][VM MemoryManager][BuildType]Conf
  
  
  I am not meant to be built.
  
  SqueakIA32BochsBuilder 
  	configureABuildFor: #ONE OF MY SUBCLASSES NAME HERE withBuildType: #build;
  	generateSources;
  	generate.  
  
  HelpBrowser openOn: CMakeVMMakerSqueakEndUserHelp
  HelpBrowser openOn: CMakeVMMakerSqueakDeveloperHelp
  
  !

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

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

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

Item was removed:
- ----- Method: SqueakIA32BochsConfig>>outputDir (in category 'squeak compatibility') -----
- outputDir
- 
- 	"the directory where built binaries will be stored"
- 	^ outputDir ifNil: [ outputDir := (self topDir / self dirOutput/ self dirInstall) ]	
- 
- !

Item was removed:
- ----- Method: SqueakIA32BochsConfig>>srcDir (in category 'squeak compatibility') -----
- srcDir
- 		^ srcDir ifNil: [ srcDir := (self topDir directoryNamed: 'src' )]!

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

Item was removed:
- ----- Method: SqueakIPhoneSqueakStackV3Config>>buildScript (in category 'build script') -----
- buildScript
- 	"answer the build script for building everything"
- 	
- 
- 	^ 
- '#!!/usr/bin/env bash
- 
- set -e 
- 
- if [ !! -e vmVersionInfo.h ]; then
- 	../scripts/extract-commit-info.sh
- fi
- cmake .
- make 
- find ../{1}/{2}.app/Contents -type f -exec mv ''\{\}'' ../{1}/{2}.app \\;
- rm -Rf ../{1}/{2}.app/Contents
- ' format: { self outputDirName. self executableName }!

Item was added:
+ ----- Method: SqueakMacOSCogV3DebugConfig>>cogitClass (in category 'source generation') -----
+ cogitClass
+ 	^ StackToRegisterMappingCogit 
+ !

Item was added:
+ ----- Method: SqueakMacOSCogV3DebugConfig>>interpreterClass (in category 'source generation') -----
+ interpreterClass
+ 	^ CoInterpreter
+ !

Item was added:
+ ----- Method: SqueakMacOSCogV3MultiThreadedConfig>>cogitClass (in category 'source generation') -----
+ cogitClass
+ 	^ StackToRegisterMappingCogit 
+ !

Item was changed:
  ----- Method: SqueakMacOSCogV3MultiThreadedConfig>>executableName (in category 'accessing') -----
  executableName
+ 	^ self vmCogExecutableName!
- 	^ 'CogMTVM'!

Item was changed:
+ SqueakMacintoshConfig subclass: #SqueakMacOSConfig
+ 	instanceVariableNames: ''
- CPlatformConfigForSqueak subclass: #SqueakMacOSConfig
- 	instanceVariableNames: 'buildType generateBuild generateBuildAssert generateBuildAssertITimerHeartbeat generateBuildDebug generateBuildDebugITimerHeartbeat generateBuildDebugMultiThreaded generateBuildIHeartbeatTimer generateBuildMultiThreaded generateBuildMultiThreadedAssert generateBuildMultiThreadedDebug'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'CMakeVMMakerSqueak-MacOS'!
  
  !SqueakMacOSConfig commentStamp: 'tty 6/15/2014 13:46' prior: 0!
  A SqueakMacOSConfig  configures a VM according to my name's form: [Operating System] [WordSize] [Processor Language][VM MemoryManager][BuildType]Conf
  
  
  I am not meant to be built.
  
  SqueakMacOSBuilder 
  	configureABuildFor: #ONE OF MY SUBCLASSES NAME HERE withBuildType: #build;
  	generateSources;
  	generate.  
  
  HelpBrowser openOn: CMakeVMMakerSqueakEndUserHelp
  HelpBrowser openOn: CMakeVMMakerSqueakDeveloperHelp
  !

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

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

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

Item was removed:
- ----- Method: SqueakMacOSConfig>>outputDir (in category 'squeak compatibility') -----
- outputDir
- 
- 	"the directory where built binaries will be stored"
- 	^ outputDir ifNil: [ outputDir := (self topDir / self dirOutput/ self dirInstall) ]	
- 
- !

Item was removed:
- ----- Method: SqueakMacOSConfig>>srcDir (in category 'squeak compatibility') -----
- srcDir
- 		^ srcDir ifNil: [ srcDir := (self topDir directoryNamed: 'src' )]!

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

Item was removed:
- ----- Method: SqueakMacOSNewspeakCogSpurConfig>>executableType (in category 'accessing') -----
- executableType
- 	^ 'MACOSX_BUNDLE'!

Item was removed:
- ----- Method: SqueakMacOSNewspeakCogSpurConfig>>prepareForGeneration (in category 'source generation') -----
- prepareForGeneration
- 	^ self prepareForCogGeneration
- !

Item was removed:
- ----- Method: SqueakMacOSNewspeakCogV3Config>>executableType (in category 'accessing') -----
- executableType
- 	^ 'MACOSX_BUNDLE'!

Item was removed:
- ----- Method: SqueakMacOSNewspeakCogV3Config>>prepareForGeneration (in category 'source generation') -----
- prepareForGeneration
- 	^ self prepareForCogGeneration
- !

Item was changed:
  ----- Method: SqueakMacOSNewspeakSistaSpurConfig>>cogitClass (in category 'source generation') -----
  cogitClass
+ 	^SistaStackToRegisterMappingCogit
+ !
- 	"answer a class for machine code generation or nil"
- 	
- 	^ StackToRegisterMappingCogit !

Item was removed:
- ----- Method: SqueakMacOSNewspeakSistaSpurConfig>>executableType (in category 'accessing') -----
- executableType
- 	^ 'MACOSX_BUNDLE'!

Item was removed:
- ----- Method: SqueakMacOSNewspeakSistaSpurConfig>>prepareForGeneration (in category 'source generation') -----
- prepareForGeneration
- 	^ self prepareForCogGeneration
- !

Item was changed:
  ----- Method: SqueakMacOSNewspeakSistaV3Config>>cogitClass (in category 'source generation') -----
  cogitClass
+ 	^SistaStackToRegisterMappingCogit
+ !
- 	"answer a class for machine code generation or nil"
- 	
- 	^ StackToRegisterMappingCogit !

Item was removed:
- ----- Method: SqueakMacOSNewspeakSistaV3Config>>executableType (in category 'accessing') -----
- executableType
- 	^ 'MACOSX_BUNDLE'!

Item was removed:
- ----- Method: SqueakMacOSNewspeakSistaV3Config>>prepareForGeneration (in category 'source generation') -----
- prepareForGeneration
- 	^ self prepareForCogGeneration
- !

Item was added:
+ ----- Method: SqueakMacOSNewspeakStackSpurConfig>>cogitClass (in category 'source generation') -----
+ cogitClass
+ 	^ StackToRegisterMappingCogit 
+ !

Item was removed:
- ----- Method: SqueakMacOSNewspeakStackSpurConfig>>prepareForGeneration (in category 'source generation') -----
- prepareForGeneration
- 	^ self prepareForStackVMGeneration
- !

Item was added:
+ ----- Method: SqueakMacOSNewspeakStackV3Config>>cogitClass (in category 'source generation') -----
+ cogitClass
+ 	^ StackToRegisterMappingCogit 
+ !

Item was removed:
- ----- Method: SqueakMacOSNewspeakStackV3Config>>prepareForGeneration (in category 'source generation') -----
- prepareForGeneration
- 	^ self prepareForStackVMGeneration
- !

Item was removed:
- ----- Method: SqueakMacOSSqueakCogSpurConfig>>executableType (in category 'accessing') -----
- executableType
- 	^ 'MACOSX_BUNDLE'!

Item was removed:
- ----- Method: SqueakMacOSSqueakCogSpurConfig>>prepareForGeneration (in category 'source generation') -----
- prepareForGeneration
- 	^ self prepareForCogGeneration
- !

Item was removed:
- ----- Method: SqueakMacOSSqueakCogV3Config>>executableType (in category 'accessing') -----
- executableType
- 	^ 'MACOSX_BUNDLE'!

Item was removed:
- ----- Method: SqueakMacOSSqueakCogV3Config>>prepareForGeneration (in category 'source generation') -----
- prepareForGeneration
- 	^ self prepareForCogGeneration
- !

Item was changed:
  ----- Method: SqueakMacOSSqueakSistaSpurConfig>>cogitClass (in category 'source generation') -----
  cogitClass
+ 	^SistaStackToRegisterMappingCogit
+ !
- 	"answer a class for machine code generation or nil"
- 	
- 	^ StackToRegisterMappingCogit !

Item was removed:
- ----- Method: SqueakMacOSSqueakSistaSpurConfig>>executableType (in category 'accessing') -----
- executableType
- 	^ 'MACOSX_BUNDLE'!

Item was removed:
- ----- Method: SqueakMacOSSqueakSistaSpurConfig>>prepareForGeneration (in category 'source generation') -----
- prepareForGeneration
- 	^ self prepareForCogGeneration
- !

Item was changed:
  ----- Method: SqueakMacOSSqueakSistaV3Config>>cogitClass (in category 'source generation') -----
  cogitClass
+ 	^SistaStackToRegisterMappingCogit
+ !
- 	"answer a class for machine code generation or nil"
- 	
- 	^ StackToRegisterMappingCogit !

Item was removed:
- ----- Method: SqueakMacOSSqueakSistaV3Config>>executableType (in category 'accessing') -----
- executableType
- 	^ 'MACOSX_BUNDLE'!

Item was removed:
- ----- Method: SqueakMacOSSqueakSistaV3Config>>prepareForGeneration (in category 'source generation') -----
- prepareForGeneration
- 	^ self prepareForCogGeneration
- !

Item was added:
+ ----- Method: SqueakMacOSSqueakStackSpurConfig>>cogitClass (in category 'source generation') -----
+ cogitClass
+ 	^ StackToRegisterMappingCogit 
+ !

Item was removed:
- ----- Method: SqueakMacOSSqueakStackSpurConfig>>prepareForGeneration (in category 'source generation') -----
- prepareForGeneration
- 	^ self prepareForStackVMGeneration
- !

Item was added:
+ ----- Method: SqueakMacOSSqueakStackV3Config>>cogitClass (in category 'source generation') -----
+ cogitClass
+ 	^ StackToRegisterMappingCogit 
+ !

Item was removed:
- ----- Method: SqueakMacOSSqueakStackV3Config>>prepareForGeneration (in category 'source generation') -----
- prepareForGeneration
- 	^ self prepareForStackVMGeneration
- !

Item was added:
+ ----- Method: SqueakMacOSStackV3DebugConfig>>cogitClass (in category 'source generation') -----
+ cogitClass
+ 	^ StackToRegisterMappingCogit 
+ !

Item was added:
+ ----- Method: SqueakMacOSStackV3DebugConfig>>interpreterClass (in category 'source generation') -----
+ interpreterClass
+ 	^ StackInterpreter!

Item was changed:
  SqueakMacOSConfig subclass: #SqueakMacOSV3Config
+ 	instanceVariableNames: ''
- 	instanceVariableNames: 'resourcesDir'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'CMakeVMMakerSqueak-MacOS'!
  
  !SqueakMacOSV3Config commentStamp: 'tty 6/15/2014 13:46' prior: 0!
  tty. This layer is should be merged with it's parent.
  
  This is an abstract class for all Mac Carbon configurations. It is intended to share code between different concrete implementations. 
  
  It is using a Carbon framework , which eventually will be replaced by Cocoa. (see CocoaIOSConfig and its subclasses).
  
  
  I am not meant to be built.
  
  SqueakMacOSBuilder 
  	configureABuildFor: #ONE OF MY SUBCLASSES NAME HERE withBuildType: #build;
  	generateSources;
  	generate.  
  
  HelpBrowser openOn: CMakeVMMakerSqueakEndUserHelp
  HelpBrowser openOn: CMakeVMMakerSqueakDeveloperHelp
  !

Item was removed:
- ----- Method: SqueakMacOSV3Config>>buildDir (in category 'directories') -----
- buildDir
- 	^ buildDir ifNil: [ buildDir := ( self topDir / self buildDirName) assureExistence].!

Item was removed:
- ----- Method: SqueakMacOSV3Config>>buildScript (in category 'build script') -----
- buildScript
- 	"answer the build script for building everything"
- 	
- 
- 	^ 
- '#!!/usr/bin/env bash
- 
- cmake .
- make
- make install
- 
- '!

Item was removed:
- ----- Method: SqueakMacOSV3Config>>compilerFlags (in category 'accessing') -----
- compilerFlags
- 	|d commonFlags flags|
- 	d:= SqueakCMakeVMMakerAbstractBuilder default buildTypeAndDirectoryInfo copy.
- 	d 
- 		at: #build put: [self compilerFlagsBuild];
- 		at: #buildAssert  put: [self compilerFlagsAssert];
- 		at: #buildAssertITimerHeartbeat  put: [self compilerFlagsAssertITimerHeartbeat];
-             at:#buildDebug  put: [self compilerFlagsDebug];   "located in CMakeVMMaker CPlatformConfig"
- 		at: #buildDebugITimerHeartbeat  put: [self compilerFlagsDebugITimerHeartbeat ];
- 		at: #buildITimerHeartbeat  put: [self compilerFlagsIHeartbeatTimer];
- 		at: #buildMultiThreaded  put: [self compilerFlagsMultiThreaded ];
- 		at: #buildMultiThreadedAssert  put: [self compilerFlagsMultiThreadedAssert];
- 		at: #buildMultiThreadedDebug   put: [self compilerFlagsMultiThreadedDebug ];
- 		at: #buildNone put:[self compilerFlagsNoBuildType].
- 
-     flags:= String streamContents: [ :stream |
- 	 (((d at:  buildType) value)  collect: #withBlanksTrimmed as: Set)
- 		asStringOn: stream 
- 		delimiter:' '].
- 
-     commonFlags:=String streamContents: [ :stream |
- 		((self commonCompilerFlags) collect: #withBlanksTrimmed as: Set)
- 			asStringOn: stream 
- 			delimiter: ' ' ].
- 	^ commonFlags, ' ' ,flags.!

Item was removed:
- ----- Method: SqueakMacOSV3Config>>executableName (in category 'accessing') -----
- executableName
- 	^ 'CogVM'!

Item was removed:
- ----- Method: SqueakMacOSV3Config>>externalModulesDir (in category 'accessing') -----
- externalModulesDir
- 	"answer the location in VM bundle, where plugins and rest of dynamic libs will be copied,
- 	by default, it is Framerowks subdir. i.e: 
- 	
- 		Cog.app/Contents/Frameworks
- 		
- 	"
- 	
- 	^ '${outputDir}/', self executableName, '.app/Contents/MacOS/Plugins'!

Item was removed:
- ----- Method: SqueakMacOSV3Config>>fixLineEndsOf: (in category 'utils') -----
- fixLineEndsOf: string
- 	^ string copyReplaceAll: String cr with: String lf!

Item was removed:
- ----- Method: SqueakMacOSV3Config>>generate (in category 'public') -----
- generate 
- 	self generatePluginsList. 
- 	self generateLicense. 
- 	"^super generate"
- 	^CMakeVMGeneratorForSqueak generate:self    "Bypass CPlatformConfig generate to invoke our compatibility class"!

Item was removed:
- ----- Method: SqueakMacOSV3Config>>generateLicense (in category 'as yet unclassified') -----
- generateLicense 
- 	self 
- 		write:  (self class licenseTemplate 
- 			format: { self version })
- 		toFile: 'LICENSE.txt'
- 	!

Item was removed:
- ----- Method: SqueakMacOSV3Config>>generatePluginsList (in category 'as yet unclassified') -----
- generatePluginsList 
- 	self 
- 		write:  (self class pluginsTemplate 
- 			format: {
- 				self version. 
- 				String streamContents: [ :stream | self internalPlugins asStringOn: stream delimiter: String cr ].
- 				String streamContents: [ :stream | self externalPlugins asStringOn: stream delimiter: String cr ].
- 				self executableName })
- 		toFile: 'PLUGINS.txt'
- 	!

Item was removed:
- ----- Method: SqueakMacOSV3Config>>outputDir (in category 'accessing') -----
- outputDir
- 
- 	"the directory where built binaries will be stored"
- 	^ outputDir ifNil: [ outputDir := (self topDir / self dirOutput/ self dirInstall) ]	
- 
- !

Item was removed:
- ----- Method: SqueakMacOSV3Config>>prepareForGeneration (in category 'source generation') -----
- prepareForGeneration
- 	!

Item was removed:
- ----- Method: SqueakMacOSV3Config>>prepareVMMaker (in category 'source generation') -----
- 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 removed:
- ----- Method: SqueakMacOSV3Config>>setupDirectories: (in category 'source generation') -----
- 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 removed:
- ----- Method: SqueakMacOSV3Config>>srcDir (in category 'accessing') -----
- srcDir
- 		^ srcDir ifNil: [ srcDir := (self topDir directoryNamed: 'src' )]!

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

Item was removed:
- ----- Method: SqueakMacOSV3Config>>validateSourcesPresent (in category 'source generation') -----
- validateSourcesPresent
- 	| sources |
- 	sources := Smalltalk sourcesName.
- 	
- 	(sources == nil)
- 		ifTrue: [	self error: 'VM source code cannot be generated without .sources file'.]		!

Item was removed:
- ----- Method: SqueakMacOSV3Config>>version (in category 'as yet unclassified') -----
- version
- 	^ ''!

Item was changed:
  SqueakMacOSConfig subclass: #SqueakMacOSX32x86Config
+ 	instanceVariableNames: ''
- 	instanceVariableNames: 'resourcesDir'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'CMakeVMMakerSqueak-MacOSX32x86'!
  
  !SqueakMacOSX32x86Config commentStamp: 'tty 6/15/2014 13:42' prior: 0!
  tty. Don't use me until I am refactored for this platform
  
  I am not sure what this does yet. I have put this here to keep a consistent pattern of top level configuration per platform.
  I need to be configured for the job I am advertised to do.
  
  
  I am not meant to be built.
  
  SqueakMacOSX32x86Builder 
  	configureABuildFor: #ONE OF MY SUBCLASSES NAME HERE withBuildType: #build;
  	generateSources;
  	generate.  
  
  HelpBrowser openOn: CMakeVMMakerSqueakEndUserHelp
  HelpBrowser openOn: CMakeVMMakerSqueakDeveloperHelp!

Item was removed:
- ----- Method: SqueakMacOSX32x86Config>>buildDir (in category 'directories') -----
- buildDir
- 	^ buildDir ifNil: [ buildDir := ( self topDir / self buildDirName) assureExistence].!

Item was removed:
- ----- Method: SqueakMacOSX32x86Config>>buildDirName (in category 'directories') -----
- buildDirName
- 	buildType isNil
- 		ifTrue:[^self dirBuildPlatform, FileDirectory slash, self dirBuildLanguageVMMM, FileDirectory slash, 'build']
- 		ifFalse:[^self dirBuildPlatform, FileDirectory slash, self dirBuildLanguageVMMM, FileDirectory slash, buildType asString]!

Item was removed:
- ----- Method: SqueakMacOSX32x86Config>>buildScript (in category 'build script') -----
- buildScript
- 	"answer the build script for building everything"
- 	
- 
- 	^ 
- '#!!/usr/bin/env bash
- 
- cmake .
- make
- make install
- 
- '!

Item was removed:
- ----- Method: SqueakMacOSX32x86Config>>compilerFlags (in category 'accessing') -----
- compilerFlags
- 	|d commonFlags flags|
- 	d:= SqueakCMakeVMMakerAbstractBuilder default buildTypeAndDirectoryInfo copy.
- 	d 
- 		at: #build put: [self compilerFlagsBuild];
- 		at: #buildAssert  put: [self compilerFlagsAssert];
- 		at: #buildAssertITimerHeartbeat  put: [self compilerFlagsAssertITimerHeartbeat];
-             at:#buildDebug  put: [self compilerFlagsDebug];   "located in CMakeVMMaker CPlatformConfig"
- 		at: #buildDebugITimerHeartbeat  put: [self compilerFlagsDebugITimerHeartbeat ];
- 		at: #buildITimerHeartbeat  put: [self compilerFlagsIHeartbeatTimer];
- 		at: #buildMultiThreaded  put: [self compilerFlagsMultiThreaded ];
- 		at: #buildMultiThreadedAssert  put: [self compilerFlagsMultiThreadedAssert];
- 		at: #buildMultiThreadedDebug   put: [self compilerFlagsMultiThreadedDebug ];
- 		at: #buildNone put:[self compilerFlagsNoBuildType].
- 
-     flags:= String streamContents: [ :stream |
- 	 (((d at:  buildType) value)  collect: #withBlanksTrimmed as: Set)
- 		asStringOn: stream 
- 		delimiter:' '].
- 
-     commonFlags:=String streamContents: [ :stream |
- 		((self commonCompilerFlags) collect: #withBlanksTrimmed as: Set)
- 			asStringOn: stream 
- 			delimiter: ' ' ].
- 	^ commonFlags, ' ' ,flags.!

Item was removed:
- ----- Method: SqueakMacOSX32x86Config>>executableName (in category 'accessing') -----
- executableName
- 	^ 'CogVM'!

Item was removed:
- ----- Method: SqueakMacOSX32x86Config>>externalModulesDir (in category 'accessing') -----
- externalModulesDir
- 	"answer the location in VM bundle, where plugins and rest of dynamic libs will be copied,
- 	by default, it is Framerowks subdir. i.e: 
- 	
- 		Cog.app/Contents/Frameworks
- 		
- 	"
- 	
- 	^ '${outputDir}/', self executableName, '.app/Contents/MacOS/Plugins'!

Item was removed:
- ----- Method: SqueakMacOSX32x86Config>>fixLineEndsOf: (in category 'utils') -----
- fixLineEndsOf: string
- 	^ string copyReplaceAll: String cr with: String lf!

Item was removed:
- ----- Method: SqueakMacOSX32x86Config>>generate (in category 'public') -----
- generate 
- 	self generatePluginsList. 
- 	self generateLicense. 
- 	"^super generate"
- 	^CMakeVMGeneratorForSqueak generate:self    "Bypass CPlatformConfig generate to invoke our compatibility class"!

Item was removed:
- ----- Method: SqueakMacOSX32x86Config>>generateLicense (in category 'as yet unclassified') -----
- generateLicense 
- 	self 
- 		write:  (self class licenseTemplate 
- 			format: { self version })
- 		toFile: 'LICENSE.txt'
- 	!

Item was removed:
- ----- Method: SqueakMacOSX32x86Config>>generatePluginsList (in category 'as yet unclassified') -----
- generatePluginsList 
- 	self 
- 		write:  (self class pluginsTemplate 
- 			format: {
- 				self version. 
- 				String streamContents: [ :stream | self internalPlugins asStringOn: stream delimiter: String cr ].
- 				String streamContents: [ :stream | self externalPlugins asStringOn: stream delimiter: String cr ].
- 				self executableName })
- 		toFile: 'PLUGINS.txt'
- 	!

Item was removed:
- ----- Method: SqueakMacOSX32x86Config>>outputDir (in category 'accessing') -----
- outputDir
- 
- 	"the directory where built binaries will be stored"
- 	^ outputDir ifNil: [ outputDir := (self topDir / self dirOutput/ self dirInstall) ]	
- 
- !

Item was removed:
- ----- Method: SqueakMacOSX32x86Config>>prepareForGeneration (in category 'source generation') -----
- prepareForGeneration
- 	!

Item was removed:
- ----- Method: SqueakMacOSX32x86Config>>prepareVMMaker (in category 'source generation') -----
- 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 removed:
- ----- Method: SqueakMacOSX32x86Config>>setupDirectories: (in category 'source generation') -----
- 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 removed:
- ----- Method: SqueakMacOSX32x86Config>>srcDir (in category 'accessing') -----
- srcDir
- 		^ srcDir ifNil: [ srcDir := (self topDir directoryNamed: 'src' )]!

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

Item was removed:
- ----- Method: SqueakMacOSX32x86Config>>validateSourcesPresent (in category 'source generation') -----
- validateSourcesPresent
- 	| sources |
- 	sources := Smalltalk sourcesName.
- 	
- 	(sources == nil)
- 		ifTrue: [	self error: 'VM source code cannot be generated without .sources file'.]		!

Item was removed:
- ----- Method: SqueakMacOSX32x86Config>>version (in category 'as yet unclassified') -----
- version
- 	^ ''!

Item was changed:
  SqueakMacOSConfig subclass: #SqueakMacOSXPowerPCConfig
+ 	instanceVariableNames: ''
- 	instanceVariableNames: 'resourcesDir'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'CMakeVMMakerSqueak-MacOSPowerPC'!
  
  !SqueakMacOSXPowerPCConfig commentStamp: 'tty 6/15/2014 13:44' prior: 0!
  tty. Don't use me until I am refactored for this platform
  
  I am not sure what this does yet. I have put this here to keep a consistent pattern of top level configuration per platform.
  I need to be configured for the job I am advertised to do.
  
  I am not meant to be built.
  
  SqueakMacOSPowerPCBuilder 
  	configureABuildFor: #ONE OF MY SUBCLASSES NAME HERE withBuildType: #build;
  	generateSources;
  	generate.  
  
  HelpBrowser openOn: CMakeVMMakerSqueakEndUserHelp
  HelpBrowser openOn: CMakeVMMakerSqueakDeveloperHelp!

Item was removed:
- ----- Method: SqueakMacOSXPowerPCConfig>>buildDir (in category 'directories') -----
- buildDir
- 	^ buildDir ifNil: [ buildDir := ( self topDir / self buildDirName) assureExistence].!

Item was removed:
- ----- Method: SqueakMacOSXPowerPCConfig>>buildDirName (in category 'directories') -----
- buildDirName
- 	buildType isNil
- 		ifTrue:[^self dirBuildPlatform, FileDirectory slash, self dirBuildLanguageVMMM, FileDirectory slash, 'build']
- 		ifFalse:[^self dirBuildPlatform, FileDirectory slash, self dirBuildLanguageVMMM, FileDirectory slash, buildType asString]!

Item was removed:
- ----- Method: SqueakMacOSXPowerPCConfig>>buildScript (in category 'build script') -----
- buildScript
- 	"answer the build script for building everything"
- 	
- 
- 	^ 
- '#!!/usr/bin/env bash
- 
- cmake .
- make
- make install
- 
- '!

Item was removed:
- ----- Method: SqueakMacOSXPowerPCConfig>>compilerFlags (in category 'accessing') -----
- compilerFlags
- 	|d commonFlags flags|
- 	d:= SqueakCMakeVMMakerAbstractBuilder default buildTypeAndDirectoryInfo copy.
- 	d 
- 		at: #build put: [self compilerFlagsBuild];
- 		at: #buildAssert  put: [self compilerFlagsAssert];
- 		at: #buildAssertITimerHeartbeat  put: [self compilerFlagsAssertITimerHeartbeat];
-             at:#buildDebug  put: [self compilerFlagsDebug];   "located in CMakeVMMaker CPlatformConfig"
- 		at: #buildDebugITimerHeartbeat  put: [self compilerFlagsDebugITimerHeartbeat ];
- 		at: #buildITimerHeartbeat  put: [self compilerFlagsIHeartbeatTimer];
- 		at: #buildMultiThreaded  put: [self compilerFlagsMultiThreaded ];
- 		at: #buildMultiThreadedAssert  put: [self compilerFlagsMultiThreadedAssert];
- 		at: #buildMultiThreadedDebug   put: [self compilerFlagsMultiThreadedDebug ];
- 		at: #buildNone put:[self compilerFlagsNoBuildType].
- 
-     flags:= String streamContents: [ :stream |
- 	 (((d at:  buildType) value)  collect: #withBlanksTrimmed as: Set)
- 		asStringOn: stream 
- 		delimiter:' '].
- 
-     commonFlags:=String streamContents: [ :stream |
- 		((self commonCompilerFlags) collect: #withBlanksTrimmed as: Set)
- 			asStringOn: stream 
- 			delimiter: ' ' ].
- 	^ commonFlags, ' ' ,flags.!

Item was removed:
- ----- Method: SqueakMacOSXPowerPCConfig>>executableName (in category 'accessing') -----
- executableName
- 	^ 'CogVM'!

Item was removed:
- ----- Method: SqueakMacOSXPowerPCConfig>>externalModulesDir (in category 'accessing') -----
- externalModulesDir
- 	"answer the location in VM bundle, where plugins and rest of dynamic libs will be copied,
- 	by default, it is Framerowks subdir. i.e: 
- 	
- 		Cog.app/Contents/Frameworks
- 		
- 	"
- 	
- 	^ '${outputDir}/', self executableName, '.app/Contents/MacOS/Plugins'!

Item was removed:
- ----- Method: SqueakMacOSXPowerPCConfig>>fixLineEndsOf: (in category 'utils') -----
- fixLineEndsOf: string
- 	^ string copyReplaceAll: String cr with: String lf!

Item was removed:
- ----- Method: SqueakMacOSXPowerPCConfig>>generate (in category 'public') -----
- generate 
- 	self generatePluginsList. 
- 	self generateLicense. 
- 	"^super generate"
- 	^CMakeVMGeneratorForSqueak generate:self    "Bypass CPlatformConfig generate to invoke our compatibility class"!

Item was removed:
- ----- Method: SqueakMacOSXPowerPCConfig>>generateLicense (in category 'accessing') -----
- generateLicense 
- 	self 
- 		write:  (self class licenseTemplate 
- 			format: { self version })
- 		toFile: 'LICENSE.txt'
- 	!

Item was removed:
- ----- Method: SqueakMacOSXPowerPCConfig>>generatePluginsList (in category 'accessing') -----
- generatePluginsList 
- 	self 
- 		write:  (self class pluginsTemplate 
- 			format: {
- 				self version. 
- 				String streamContents: [ :stream | self internalPlugins asStringOn: stream delimiter: String cr ].
- 				String streamContents: [ :stream | self externalPlugins asStringOn: stream delimiter: String cr ].
- 				self executableName })
- 		toFile: 'PLUGINS.txt'
- 	!

Item was removed:
- ----- Method: SqueakMacOSXPowerPCConfig>>outputDir (in category 'accessing') -----
- outputDir
- 
- 	"the directory where built binaries will be stored"
- 	^ outputDir ifNil: [ outputDir := (self topDir / self dirOutput/ self dirInstall) ]	
- 
- !

Item was removed:
- ----- Method: SqueakMacOSXPowerPCConfig>>prepareForGeneration (in category 'source generation') -----
- prepareForGeneration
- 	!

Item was removed:
- ----- Method: SqueakMacOSXPowerPCConfig>>prepareVMMaker (in category 'source generation') -----
- 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 removed:
- ----- Method: SqueakMacOSXPowerPCConfig>>setupDirectories: (in category 'source generation') -----
- 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 removed:
- ----- Method: SqueakMacOSXPowerPCConfig>>srcDir (in category 'accessing') -----
- srcDir
- 		^ srcDir ifNil: [ srcDir := (self topDir directoryNamed: 'src' )]!

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

Item was removed:
- ----- Method: SqueakMacOSXPowerPCConfig>>validateSourcesPresent (in category 'source generation') -----
- validateSourcesPresent
- 	| sources |
- 	sources := Smalltalk sourcesName.
- 	
- 	(sources == nil)
- 		ifTrue: [	self error: 'VM source code cannot be generated without .sources file'.]		!

Item was removed:
- ----- Method: SqueakMacOSXPowerPCConfig>>version (in category 'accessing') -----
- version
- 	^ ''!

Item was added:
+ ----- Method: SqueakMacOSXPowerPCNewspeakCogSpur>>cogitClass (in category 'source generation') -----
+ cogitClass
+ 	^ StackToRegisterMappingCogit 
+ !

Item was added:
+ ----- Method: SqueakMacOSXPowerPCNewspeakCogSpur>>interpreterClass (in category 'source generation') -----
+ interpreterClass
+ 	^ CoInterpreter
+ !

Item was added:
+ ----- Method: SqueakMacOSXPowerPCNewspeakCogV3>>cogitClass (in category 'source generation') -----
+ cogitClass
+ 	^ StackToRegisterMappingCogit 
+ !

Item was added:
+ ----- Method: SqueakMacOSXPowerPCNewspeakCogV3>>interpreterClass (in category 'source generation') -----
+ interpreterClass
+ 	^ CoInterpreter
+ !

Item was added:
+ ----- Method: SqueakMacOSXPowerPCNewspeakSistaSpur>>cogitClass (in category 'source generation') -----
+ cogitClass
+ 	^SistaStackToRegisterMappingCogit
+ !

Item was added:
+ ----- Method: SqueakMacOSXPowerPCNewspeakSistaSpur>>interpreterClass (in category 'source generation') -----
+ interpreterClass
+ 	^ CoInterpreter
+ !

Item was added:
+ ----- Method: SqueakMacOSXPowerPCNewspeakSistaV3>>cogitClass (in category 'source generation') -----
+ cogitClass
+ 	^SistaStackToRegisterMappingCogit
+ !

Item was added:
+ ----- Method: SqueakMacOSXPowerPCNewspeakSistaV3>>interpreterClass (in category 'source generation') -----
+ interpreterClass
+ 	^ CoInterpreter
+ !

Item was added:
+ ----- Method: SqueakMacOSXPowerPCNewspeakStackSpur>>cogitClass (in category 'source generation') -----
+ cogitClass
+ 	^ StackToRegisterMappingCogit 
+ !

Item was added:
+ ----- Method: SqueakMacOSXPowerPCNewspeakStackSpur>>interpreterClass (in category 'source generation') -----
+ interpreterClass
+ 	^ StackInterpreter!

Item was added:
+ ----- Method: SqueakMacOSXPowerPCNewspeakStackV3>>cogitClass (in category 'source generation') -----
+ cogitClass
+ 	^ StackToRegisterMappingCogit 
+ !

Item was added:
+ ----- Method: SqueakMacOSXPowerPCNewspeakStackV3>>interpreterClass (in category 'source generation') -----
+ interpreterClass
+ 	^ StackInterpreter!

Item was added:
+ ----- Method: SqueakMacOSXPowerPCSqueakCogSpur>>cogitClass (in category 'source generation') -----
+ cogitClass
+ 	^ StackToRegisterMappingCogit 
+ !

Item was added:
+ ----- Method: SqueakMacOSXPowerPCSqueakCogSpur>>interpreterClass (in category 'source generation') -----
+ interpreterClass
+ 	^ CoInterpreter
+ !

Item was added:
+ ----- Method: SqueakMacOSXPowerPCSqueakCogV3>>cogitClass (in category 'source generation') -----
+ cogitClass
+ 	^ StackToRegisterMappingCogit 
+ !

Item was added:
+ ----- Method: SqueakMacOSXPowerPCSqueakCogV3>>interpreterClass (in category 'source generation') -----
+ interpreterClass
+ 	^ CoInterpreter
+ !

Item was added:
+ ----- Method: SqueakMacOSXPowerPCSqueakSistaSpur>>cogitClass (in category 'source generation') -----
+ cogitClass
+ 	^SistaStackToRegisterMappingCogit
+ !

Item was added:
+ ----- Method: SqueakMacOSXPowerPCSqueakSistaSpur>>interpreterClass (in category 'source generation') -----
+ interpreterClass
+ 	^ CoInterpreter
+ !

Item was added:
+ ----- Method: SqueakMacOSXPowerPCSqueakSistaV3>>cogitClass (in category 'source generation') -----
+ cogitClass
+ 	^SistaStackToRegisterMappingCogit
+ !

Item was added:
+ ----- Method: SqueakMacOSXPowerPCSqueakSistaV3>>interpreterClass (in category 'source generation') -----
+ interpreterClass
+ 	^ CoInterpreter
+ !

Item was added:
+ ----- Method: SqueakMacOSXPowerPCSqueakStackSpur>>cogitClass (in category 'source generation') -----
+ cogitClass
+ 	^ StackToRegisterMappingCogit 
+ !

Item was added:
+ ----- Method: SqueakMacOSXPowerPCSqueakStackSpur>>interpreterClass (in category 'source generation') -----
+ interpreterClass
+ 	^ StackInterpreter!

Item was added:
+ ----- Method: SqueakMacOSXPowerPCSqueakStackV3>>cogitClass (in category 'source generation') -----
+ cogitClass
+ 	^ StackToRegisterMappingCogit 
+ !

Item was added:
+ ----- Method: SqueakMacOSXPowerPCSqueakStackV3>>interpreterClass (in category 'source generation') -----
+ interpreterClass
+ 	^ StackInterpreter!

Item was changed:
  CPlatformConfigForSqueak subclass: #SqueakMacintoshConfig
+ 	instanceVariableNames: 'resourcesDir'
- 	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'CMakeVMMakerSqueak'!

Item was added:
+ ----- Method: SqueakMacintoshConfig>>externalModulesDir (in category 'accessing') -----
+ externalModulesDir
+ 	"answer the location in VM bundle, where plugins and rest of dynamic libs will be copied,
+ 	by default, it is Framerowks subdir. i.e: 
+ 	
+ 		Cog.app/Contents/Frameworks
+ 		
+ 	"
+ 	
+ 	^ '${outputDir}/', self executableName, '.app/Contents/MacOS/Plugins'!

Item was changed:
+ SqueakUnixConfig subclass: #SqueakSunOS32x86Config
+ 	instanceVariableNames: ''
- CPlatformConfigForSqueak subclass: #SqueakSunOS32x86Config
- 	instanceVariableNames: 'buildType generateBuild generateBuildAssert generateBuildAssertITimerHeartbeat generateBuildDebug generateBuildDebugITimerHeartbeat generateBuildDebugMultiThreaded generateBuildIHeartbeatTimer generateBuildMultiThreaded generateBuildMultiThreadedAssert generateBuildMultiThreadedDebug'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'CMakeVMMakerSqueak-SunOS32x86'!
  
  !SqueakSunOS32x86Config commentStamp: 'tty 6/15/2014 13:41' prior: 0!
  A SqueakSunOS32x86CogConfig provides common informatin for my subclasses.
  
  I am not meant to be built.
  
  SqueakSunOS32x86Builder 
  	configureABuildFor: #ONE OF MY SUBCLASSES NAME HERE withBuildType: #build;
  	generateSources;
  	generate.  
  
  HelpBrowser openOn: CMakeVMMakerSqueakEndUserHelp
  HelpBrowser openOn: CMakeVMMakerSqueakDeveloperHelp!

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

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

Item was removed:
- ----- Method: SqueakSunOS32x86Config>>buildType: (in category 'squeak compatibility') -----
- buildType: aSymbol
- 	buildType:= aSymbol!

Item was removed:
- ----- Method: SqueakSunOS32x86Config>>outputDir (in category 'squeak compatibility') -----
- outputDir
- 
- 	"the directory where built binaries will be stored"
- 	^ outputDir ifNil: [ outputDir := (self topDir / self dirOutput/ self dirInstall) ]	
- 
- !

Item was removed:
- ----- Method: SqueakSunOS32x86Config>>srcDir (in category 'squeak compatibility') -----
- srcDir
- 		^ srcDir ifNil: [ srcDir := (self topDir directoryNamed: 'src' )]!

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

Item was added:
+ ----- Method: SqueakSunOS32x86NewspeakCogSpurConfig>>cogitClass (in category 'source generation') -----
+ cogitClass
+ 	^ StackToRegisterMappingCogit !

Item was added:
+ ----- Method: SqueakSunOS32x86NewspeakCogSpurConfig>>interpreterClass (in category 'source generation') -----
+ interpreterClass
+ 	^ CoInterpreter
+ !

Item was added:
+ ----- Method: SqueakSunOS32x86NewspeakCogV3Config>>cogitClass (in category 'source generation') -----
+ cogitClass
+ 	^ StackToRegisterMappingCogit !

Item was added:
+ ----- Method: SqueakSunOS32x86NewspeakCogV3Config>>interpreterClass (in category 'source generation') -----
+ interpreterClass
+ 	^ CoInterpreter
+ !

Item was added:
+ ----- Method: SqueakSunOS32x86NewspeakSistaSpurConfig>>cogitClass (in category 'source generation') -----
+ cogitClass
+ 	^SistaStackToRegisterMappingCogit
+ !

Item was added:
+ ----- Method: SqueakSunOS32x86NewspeakSistaSpurConfig>>interpreterClass (in category 'source generation') -----
+ interpreterClass
+ 	^ CoInterpreter
+ !

Item was added:
+ ----- Method: SqueakSunOS32x86NewspeakSistaV3Config>>cogitClass (in category 'source generation') -----
+ cogitClass
+ 	^SistaStackToRegisterMappingCogit
+ !

Item was added:
+ ----- Method: SqueakSunOS32x86NewspeakSistaV3Config>>interpreterClass (in category 'source generation') -----
+ interpreterClass
+ 	^ CoInterpreter
+ !

Item was added:
+ ----- Method: SqueakSunOS32x86NewspeakStackSpurConfig>>cogitClass (in category 'source generation') -----
+ cogitClass
+ 	^ StackToRegisterMappingCogit !

Item was added:
+ ----- Method: SqueakSunOS32x86NewspeakStackSpurConfig>>interpreterClass (in category 'source generation') -----
+ interpreterClass
+ 	^ StackInterpreter!

Item was added:
+ ----- Method: SqueakSunOS32x86NewspeakStackV3Config>>cogitClass (in category 'source generation') -----
+ cogitClass
+ 	^ StackToRegisterMappingCogit !

Item was added:
+ ----- Method: SqueakSunOS32x86NewspeakStackV3Config>>interpreterClass (in category 'source generation') -----
+ interpreterClass
+ 	^ StackInterpreter!

Item was added:
+ ----- Method: SqueakSunOS32x86SqueakCogSpurConfig>>cogitClass (in category 'source generation') -----
+ cogitClass
+ 	^ StackToRegisterMappingCogit !

Item was added:
+ ----- Method: SqueakSunOS32x86SqueakCogSpurConfig>>interpreterClass (in category 'source generation') -----
+ interpreterClass
+ 	^ CoInterpreter
+ !

Item was added:
+ ----- Method: SqueakSunOS32x86SqueakCogV3Config>>cogitClass (in category 'source generation') -----
+ cogitClass
+ 	^ StackToRegisterMappingCogit !

Item was added:
+ ----- Method: SqueakSunOS32x86SqueakCogV3Config>>interpreterClass (in category 'source generation') -----
+ interpreterClass
+ 	^ CoInterpreter
+ !

Item was added:
+ ----- Method: SqueakSunOS32x86SqueakSistaSpurConfig>>cogitClass (in category 'source generation') -----
+ cogitClass
+ 	^SistaStackToRegisterMappingCogit
+ !

Item was added:
+ ----- Method: SqueakSunOS32x86SqueakSistaSpurConfig>>interpreterClass (in category 'source generation') -----
+ interpreterClass
+ 	^ CoInterpreter
+ !

Item was added:
+ ----- Method: SqueakSunOS32x86SqueakSistaV3Config>>cogitClass (in category 'source generation') -----
+ cogitClass
+ 	^SistaStackToRegisterMappingCogit
+ !

Item was added:
+ ----- Method: SqueakSunOS32x86SqueakSistaV3Config>>interpreterClass (in category 'source generation') -----
+ interpreterClass
+ 	^ CoInterpreter
+ !

Item was added:
+ ----- Method: SqueakSunOS32x86SqueakStackSpurConfig>>cogitClass (in category 'source generation') -----
+ cogitClass
+ 	^ StackToRegisterMappingCogit !

Item was added:
+ ----- Method: SqueakSunOS32x86SqueakStackSpurConfig>>interpreterClass (in category 'source generation') -----
+ interpreterClass
+ 	^ StackInterpreter!

Item was added:
+ ----- Method: SqueakSunOS32x86SqueakStackV3Config>>cogitClass (in category 'source generation') -----
+ cogitClass
+ 	^ StackToRegisterMappingCogit !

Item was added:
+ ----- Method: SqueakSunOS32x86SqueakStackV3Config>>interpreterClass (in category 'source generation') -----
+ interpreterClass
+ 	^ StackInterpreter!

Item was added:
+ ----- Method: SqueakUnixConfig>>commonCompilerFlags (in category 'compiler flags') -----
+ commonCompilerFlags
+ 
+ 	"Common compiler flags
+ 	
+ 	
+ 	LSB_FIRST=1 means that target platform is little endian. 
+ 	set it to 0 for big-endian platforms
+ 	
+ 	"
+ 	
+ 	^ {
+ 		'-DLSB_FIRST=1'. 
+ 		'-DUSE_GLOBAL_STRUCT=0'. 
+ 		'-DCOGMTVM=0'. 
+ 		'-m32'.
+ 		'-DENABLE_FAST_BLT ' } 	
+ 	!

Item was added:
+ ----- Method: SqueakUnixConfig>>configH (in category 'headers generation') -----
+ configH
+ "ONLY USED ON UNIX CONFIGS included here for completeness and consistency CogUnixConfig browse.
+ "
+ "
+ Use  configH to tell your plugins where to find its libraries etc.
+ The version of this is platform dependent.
+ You may also need to edit your oscogvm/platforms/YOUR PLATFORM/plugins/ThePLuginDirectory/acinclude.m4 file so that it conforms to your system.
+ 
+ tty needed a custom version of this in Linux32x86SqueakCogV3NoGLConfig in order to build the UUIDPlugin.
+ 
+ Go to oscogvm/platforms/YOUR PLATFORM/plugins/ThePLuginDirectory and look at the acinclude.m4 file
+ you may need to edit that .
+ 
+ NOTE: CPlatformConfig contains a useable version of this that you can modify. 
+ 
+ I reproduce it here, but with double quotes changed to two single quotes so that the commenting will hold.
+ I provide a <---N.B quotes need changing at each place they have been modified.
+ 
+ Again. it is easier to copy the one in CPlatformConfig.
+ 
+ 
+ 	^ '
+ #ifndef __sq_config_h
+ #define __sq_config_h
+ 
+ /* explicit image width */
+ 
+ #define HAVE_INTERP_H 1
+ 
+ /* package options */
+ 
+ #define USE_X11 1
+ #define USE_X11_GLX 1
+ /* #undef       USE_QUARTZ */
+ /* #undef       USE_QUARTZ_CGL */
+ /* #undef       USE_RFB */
+ 
+ /* libraries */
+ 
+ /* #undef       HAVE_LIBX11 */
+ #define HAVE_LIBXEXT 1
+ #define HAVE_LIBDL 1
+ /* #undef       HAVE_DYLD */
+ /* #undef       HAVE_LIBFFI */
+ /* #undef       HAVE_ICONV */
+ 
+ /* #undef       USE_AUDIO_NONE */
+ /* #undef       USE_AUDIO_SUN */
+ /* #undef       USE_AUDIO_NAS */
+ /* #undef       USE_AUDIO_OSS */
+ /* #undef       USE_AUDIO_MACOSX */
+ /* #undef       OSS_DEVICE */
+ 
+ /* header files */
+ 
+ #define HAVE_UNISTD_H 1
+ /* #undef       NEED_GETHOSTNAME_P */
+ 
+ #define HAVE_DIRENT_H 1
+ /* #undef       HAVE_SYS_NDIR_H */
+ /* #undef       HAVE_SYS_DIR_H */
+ /* #undef       HAVE_NDIR_H */
+ #define HAVE_DLFCN_H 1
+ /* #undef       HAVE_ICONV_H */
+ 
+ #define HAVE_SYS_TIME_H 1
+ #define TIME_WITH_SYS_TIME 1
+ 
+ #define HAVE_SYS_FILIO_H 1
+ 
+ /* #undef       HAVE_SYS_AUDIOIO_H */
+ /* #undef       HAVE_SUN_AUDIOIO_H */
+ 
+ /* #undef       HAVE_PTY_H */
+ /* #undef       HAVE_UTIL_H */
+ #define HAVE_LIBUTIL_H 1
+ /* #undef       HAVE_STROPTS_H */
+ 
+ #define HAVE_GL_GL_H 1
+ /* #undef       HAVE_OPENGL_GL_H */
+ 
+ /* #undef       NEED_SUNOS_H */
+ 
+ 
+ #define HAVE_UUID_H
+ /* system calls/library functions */
+ 
+ #define AT_EXIT atexit
+ 
+ #define HAVE_TZSET 1
+ 
+ #define HAVE_OPENPTY 1
+ /* #undef       HAVE_UNIX98_PTYS */
+ 
+ #define HAVE_SNPRINTF 1
+ /* #undef       HAVE___SNPRINTF */
+ 
+ #define HAVE_MMAP 1
+ 
+ /* #undef       HAVE_DYLD */
+ 
+ #define HAVE_LANGINFO_CODESET 1
+ 
+ #define HAVE_ALLOCA 1
+ /* #undef       HAVE_ALLOCA_H */
+ 
+ #define HAVE_UNSETENV 1
+ 
+ #define HAVE_NANOSLEEP 1
+ 
+ /* widths of primitive types */
+ 
+ #define SIZEOF_INT 4
+ #define SIZEOF_LONG 4
+ #define SIZEOF_LONG_LONG 8
+ #define SIZEOF_VOID_P 4
+ 
+ /* structures */
+ 
+ #define HAVE_TM_GMTOFF 1
+ #define HAVE_TIMEZONE 1
+ 
+ /* typedefs */
+ 
+ /* #undef       size_t */
+ /* #undef       socklen_t */
+ 
+ #define squeakInt64 long long
+ 
+ /* architecture */
+ 
+ #define OS_TYPE ''unix''    <---N.B quotes need changing at each place they have been modifying.
+ 
+ #define VM_HOST ''i386-freebsd8.2''    <---N.B quotes need changing at each place they have been modifying.
+ #define VM_HOST_CPU ''i386''    <---N.B quotes need changing at each place they have been modifying.
+ /* #undef       VM_HOST_VENDOR */
+ #define VM_HOST_OS ''freebsd8.2''   <---N.B quotes need changing at each place they have been modifying.
+ #define VM_BUILD_STRING ''Unix built on ''__DATE__ '' ''__TIME__'' Compiler: ''__VERSION__          <---N.B quotes need changing at each place they have been modifying.
+ 
+ /* #undef       WORDS_BIGENDIAN */
+ /* #undef       DOUBLE_WORD_ALIGNMENT */
+ 
+ /* damage containment */
+ 
+ /* #undef       DARWIN */
+ 
+ #ifdef NEED_SUNOS_H
+ # include ''sunos.h''    <---N.B quotes need changing at each place they have been modifying.
+ #endif
+ 
+ /* other configured variables */
+ 
+ #define SQ_VERSION ''3.9a-7024''    <---N.B quotes need changing at each place they have been modifying.
+ #define VM_VERSION ''3.9-7''    <---N.B quotes need changing at each place they have been modifying.
+ #define VM_MODULE_PREFIX ''    <---N.B quotes need changing at each place they have been modifying.
+ /* #undef VM_DLSYM_PREFIX */    
+ #define VM_X11DIR '/usr/X11R6/lib'    <---N.B quotes need changing at each place they have been modifying.
+ 
+ /* avoid dependencies on glibc2.3 */
+ 
+ /* #undef HAVE_FEATURES_H */
+ 
+ #if defined(HAVE_FEATURES_H)
+ # include ''glibc.h''    <---N.B quotes need changing at each place they have been modifying.
+ #endif
+ 
+ #endif /* __sq_config_h */
+ 																																																																					
+ 																																																																				'
+ "!

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

Item was added:
+ ----- Method: SqueakUnixConfig>>externalModulesDir (in category 'accessing') -----
+ externalModulesDir
+ 	"answer the location in VM bundle, where plugins and rest of dynamic libs will be copied,
+ 	"
+ 	^ '${outputDir}'!

Item was added:
+ ----- Method: SqueakUnixConfig>>frameworks (in category 'accessing') -----
+ frameworks
+ 	"leave empty for all platforms but Mac OS"
+ 	^ #()!

Item was added:
+ ----- Method: SqueakUnixConfig>>setupDirectories: (in category 'squeak compatability') -----
+ setupDirectories: gen
+ 	super setupDirectories: gen.
+ 	gen set: #externalModulesDir toString: self externalModulesDir.!

Item was changed:
+ SqueakWindowsConfig subclass: #SqueakWin32x86Config
+ 	instanceVariableNames: ''
- CPlatformConfigForSqueak subclass: #SqueakWin32x86Config
- 	instanceVariableNames: 'buildType generateBuild generateBuildAssert generateBuildAssertITimerHeartbeat generateBuildDebug generateBuildDebugITimerHeartbeat generateBuildDebugMultiThreaded generateBuildIHeartbeatTimer generateBuildMultiThreaded generateBuildMultiThreadedAssert generateBuildMultiThreadedDebug'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'CMakeVMMakerSqueak-Win32x86'!
  
  !SqueakWin32x86Config commentStamp: 'tty 6/15/2014 13:37' prior: 0!
  N.B. tty.  This class comment is from my pharo parent..
  
  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.
  !

Item was removed:
- ----- Method: SqueakWin32x86Config>>buildDir (in category 'directories') -----
- buildDir
- 	^ buildDir ifNil: [ buildDir := ( self topDir / self buildDirName) assureExistence].!

Item was removed:
- ----- Method: SqueakWin32x86Config>>buildDirName (in category 'directories') -----
- buildDirName
- 	buildType isNil
- 		ifTrue:[^self dirBuildPlatform, FileDirectory slash, self dirBuildLanguageVMMM, FileDirectory slash, 'build']
- 		ifFalse:[^self dirBuildPlatform, FileDirectory slash, self dirBuildLanguageVMMM, FileDirectory slash, buildType asString]!

Item was removed:
- ----- Method: SqueakWin32x86Config>>buildType: (in category 'squeak compatibility') -----
- buildType: aSymbol
- 	buildType:=aSymbol!

Item was removed:
- ----- Method: SqueakWin32x86Config>>commonCompilerFlags (in category 'compiler flags') -----
- commonCompilerFlags
- 	"omit -ggdb2 to prevent generating debug info"
- 	"Some flags explanation: 
- 	
- 	STACK_ALIGN_BYTES=16 is needed in mingw and FFI (and I suppose on other modules too).
- 	DALLOCA_LIES_SO_USE_GETSP=0 Some compilers return the stack address+4 on alloca function, 
- 	then FFI module needs to adjust that. It is NOT the case of mingw.
- 	For more information see this thread: http://forum.world.st/There-are-something-fishy-with-FFI-plugin-td4584226.html
- 	"
- 	^ {  
- 		'-march=pentium4'.
- 		'-mwindows'.
- 		'-D_MT'.
- 		'-msse2'. 
- 		'-mthreads'. 
- 		'-mwin32'.
- 		'-mno-rtd'. 
- 		'-mms-bitfields'. 
- 		'-mno-accumulate-outgoing-args ', self winVer.
- 		'-DWIN32'. 
- 		'-DWIN32_FILE_SUPPORT'. 
- 		'-DNO_ISNAN'.
- 		'-DNO_SERVICE'. 
- 		'-DNO_STD_FILE_SUPPORT'.
- 		'-DLSB_FIRST'. 
- 		'-DVM_NAME="', self executableName,'"'.
- 		'-DX86 '.
- 		'-DSTACK_ALIGN_BYTES=16'. 
- 		'-DALLOCA_LIES_SO_USE_GETSP=0'. 
- 		'-DENABLE_FAST_BLT ' }!

Item was removed:
- ----- Method: SqueakWin32x86Config>>compilerFlags (in category 'directories') -----
- compilerFlags
- 	|d commonFlags flags|
- 	d:= SqueakCMakeVMMakerAbstractBuilder default buildTypeAndDirectoryInfo copy.
- 	d 
- 		at: #build put: [self compilerFlagsBuild];
- 		at: #buildAssert  put: [self compilerFlagsAssert];
- 		at: #buildAssertITimerHeartbeat  put: [self compilerFlagsAssertITimerHeartbeat];
-             at:#buildDebug  put: [self compilerFlagsDebug];   "located in CMakeVMMaker CPlatformConfig"
- 		at: #buildDebugITimerHeartbeat  put: [self compilerFlagsDebugITimerHeartbeat ];
- 		at: #buildITimerHeartbeat  put: [self compilerFlagsIHeartbeatTimer];
- 		at: #buildMultiThreaded  put: [self compilerFlagsMultiThreaded ];
- 		at: #buildMultiThreadedAssert  put: [self compilerFlagsMultiThreadedAssert];
- 		at: #buildMultiThreadedDebug   put: [self compilerFlagsMultiThreadedDebug ];
- 		at: #buildNone put:[self compilerFlagsNoBuildType].
- 
-     flags:= String streamContents: [ :stream |
- 	 (((d at:  buildType) value)  collect: #withBlanksTrimmed as: Set)
- 		asStringOn: stream 
- 		delimiter:' '].
- 
-     commonFlags:=String streamContents: [ :stream |
- 		((self commonCompilerFlags) collect: #withBlanksTrimmed as: Set)
- 			asStringOn: stream 
- 			delimiter: ' ' ].
- 	^ commonFlags, ' ' ,flags.!

Item was removed:
- ----- Method: SqueakWin32x86Config>>executableType (in category 'accessing') -----
- executableType
- 	^ 'WIN32'!

Item was removed:
- ----- Method: SqueakWin32x86Config>>externalModulesDir (in category 'accessing') -----
- externalModulesDir
- 	"answer the location in VM bundle, where plugins and rest of dynamic libs will be copied,
- 	"
- 	^ '${outputDir}'!

Item was removed:
- ----- Method: SqueakWin32x86Config>>fixLineEndsOf: (in category 'utils') -----
- fixLineEndsOf: string
- 	^ string copyReplaceAll: String cr with: String crlf!

Item was removed:
- ----- Method: SqueakWin32x86Config>>generate (in category 'public') -----
- generate 
- 	self generatePluginsList. 
- 	self generateLicense. 
- 	"^super generate"
- 	^CMakeVMGeneratorForSqueak generate:self    "Bypass CPlatformConfig generate to invoke our compatibility class"!

Item was removed:
- ----- Method: SqueakWin32x86Config>>msysPathFor: (in category 'accessing') -----
- msysPathFor: aPath
- 	| path |
- 	self flag:'tty'. "code smell alert"
- 	^aPath isString
- 		ifTrue:[	path := aPath  copyReplaceAll: '\' with: '/'.]
- 		ifFalse:[	path := aPath pathName copyReplaceAll: '\' with: '/'.]
- 
- 	
- !

Item was removed:
- ----- Method: SqueakWin32x86Config>>outputDir (in category 'directories') -----
- outputDir
- 
- 	"the directory where built binaries will be stored"
- 	^ outputDir ifNil: [ outputDir := (self topDir / self dirOutput/ self dirInstall) ]	
- 
- !

Item was removed:
- ----- Method: SqueakWin32x86Config>>platformName (in category 'accessing') -----
- platformName
- 	^ 'win32'!

Item was removed:
- ----- Method: SqueakWin32x86Config>>prepareVMMaker (in category 'source generation') -----
- 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 removed:
- ----- Method: SqueakWin32x86Config>>setGlobalOptionsAfterDetermineSystem:buildType: (in category 'utils') -----
- setGlobalOptionsAfterDetermineSystem: aMaker buildType: aBuildType
- 	"invoke correct setGlobalOptions for this buildType to allow per-buildType customization'"
- 
- 	|d |
- 	d:= SqueakCMakeVMMakerAbstractBuilder default buildTypeAndDirectoryInfo copy.
- 	d 
- 		at: #build put: [self setGlobalOptionsAfterDetermineSystemBuild: aMaker];
- 		at: #buildAssert  put: [self setGlobalOptionsAfterDetermineSystemBuildAssert: aMaker];
- 		at: #buildAssertITimerHeartbeat  put: [self setGlobalOptionsAfterDetermineSystemBuildAssertITimerHeartbeat: aMaker];
-             at:#buildDebug  put: [self setGlobalOptionsAfterDetermineSystemBuildDebug: aMaker];   
- 		at: #buildITimerHeartbeat  put: [self setGlobalOptionsAfterDetermineSystemBuildITimerHeartbeat: aMaker];
- 		at: #buildMultiThreaded  put: [self setGlobalOptionsAfterDetermineSystemBuildMultiThreaded: aMaker ];
- 		at: #buildMultiThreadedAssert  put: [self setGlobalOptionsAfterDetermineSystemBuildMultiThreadedAssert: aMaker];
- 		at: #buildMultiThreadedDebug   put: [self setGlobalOptionsAfterDetermineSystemBuildMultiThreadedDebug: aMaker ];
- 		at: #buildNone put:[self setGlobalOptionsBuildNone: aMaker].
- 
- 	 ^(d at: ( aBuildType)) value
- !

Item was removed:
- ----- Method: SqueakWin32x86Config>>setupDirectories: (in category 'directories') -----
- setupDirectories: gen
- 	"we have to override that, because we need to convert windoze paths to msys ones"
- 	| dirsInclude |
- 	
- 	" write the directories in separate include file"
- 	dirsInclude := gen captureOutputDuring: [
- 		gen
- 			set: #topDir toString: (self msysPathFor: self topDir fullName); 
- 			set: #buildDir toString: (self buildDir ifNil: ['${topDir}/build'] ifNotNil:[ self msysPathFor: self buildDir fullName ]);
- 			set: #thirdpartyDir toString: '${buildDir}/thirdparty';
- 			set: #platformsDir toString: (self msysPathFor: self platformsDir);
- 			set: #srcDir toString: (self msysPathFor: self srcDir);
- 			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 msysPathFor: self outputDir).
- 	].
- 
- 	self write: dirsInclude toFile: 'directories.cmake'.
- 	
- 	gen include: 'directories.cmake'.
- 	
- 	gen set: #externalModulesDir toString: self externalModulesDir.
- !

Item was removed:
- ----- Method: SqueakWin32x86Config>>srcDir (in category 'accessing') -----
- srcDir
- 		^ srcDir ifNil: [ srcDir := (self topDir directoryNamed: 'src' )]!

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

Item was removed:
- ----- Method: SqueakWin32x86Config>>validateSourcesPresent (in category 'source generation') -----
- validateSourcesPresent
- 	| sources |
- 	sources := Smalltalk sourcesName.
- 	
- 	(sources == nil)
- 		ifTrue: [	self error: 'VM source code cannot be generated without .sources file'.]		!

Item was removed:
- ----- Method: SqueakWin32x86Config>>winVer (in category 'accessing') -----
- winVer
- 	"Set minimum version to WindowsXP (see /cygwin/usr/include//w32api/w32api.h)"
- 	
- 	^ '-D_WIN32_WINNT=0x0501 -DWINVER=0x0501'!

Item was added:
+ ----- Method: SqueakWindowsConfig>>commonCompilerFlags (in category 'compiler flags') -----
+ commonCompilerFlags
+ 	"omit -ggdb2 to prevent generating debug info"
+ 	"Some flags explanation: 
+ 	
+ 	STACK_ALIGN_BYTES=16 is needed in mingw and FFI (and I suppose on other modules too).
+ 	DALLOCA_LIES_SO_USE_GETSP=0 Some compilers return the stack address+4 on alloca function, 
+ 	then FFI module needs to adjust that. It is NOT the case of mingw.
+ 	For more information see this thread: http://forum.world.st/There-are-something-fishy-with-FFI-plugin-td4584226.html
+ 	"
+ 	^ {  
+ 		'-march=pentium4'.
+ 		'-mwindows'.
+ 		'-D_MT'.
+ 		'-msse2'. 
+ 		'-mthreads'. 
+ 		'-mwin32'.
+ 		'-mno-rtd'. 
+ 		'-mms-bitfields'. 
+ 		'-mno-accumulate-outgoing-args ', self winVer.
+ 		'-DWIN32'. 
+ 		'-DWIN32_FILE_SUPPORT'. 
+ 		'-DNO_ISNAN'.
+ 		'-DNO_SERVICE'. 
+ 		'-DNO_STD_FILE_SUPPORT'.
+ 		'-DLSB_FIRST'. 
+ 		'-DVM_NAME="', self executableName,'"'.
+ 		'-DX86 '.
+ 		'-DSTACK_ALIGN_BYTES=16'. 
+ 		'-DALLOCA_LIES_SO_USE_GETSP=0'. 
+ 		'-DENABLE_FAST_BLT ' }!

Item was added:
+ ----- Method: SqueakWindowsConfig>>executableType (in category 'accessing') -----
+ executableType
+ 	^ 'WIN32'!

Item was added:
+ ----- Method: SqueakWindowsConfig>>externalModulesDir (in category 'accessing') -----
+ externalModulesDir
+ 	"answer the location in VM bundle, where plugins and rest of dynamic libs will be copied,
+ 	"
+ 	^ '${outputDir}'!

Item was added:
+ ----- Method: SqueakWindowsConfig>>frameworks (in category 'accessing') -----
+ frameworks
+ 	"leave empty for all platforms but Mac OS"
+ 	^ #()!

Item was added:
+ ----- Method: SqueakWindowsConfig>>msysPathFor: (in category 'accessing') -----
+ msysPathFor: aPath
+ 	| path |
+ 	self flag:'tty'. "code smell alert"
+ 	^aPath isString
+ 		ifTrue:[	path := aPath  copyReplaceAll: '\' with: '/'.]
+ 		ifFalse:[	path := aPath pathName copyReplaceAll: '\' with: '/'.]
+ 
+ 	
+ !

Item was added:
+ ----- Method: SqueakWindowsConfig>>winVer (in category 'accessing') -----
+ winVer
+ 	"Set minimum version to WindowsXP (see /cygwin/usr/include//w32api/w32api.h)"
+ 	
+ 	^ '-D_WIN32_WINNT=0x0501 -DWINVER=0x0501'!

Item was removed:
- ----- Method: Win32x86NewspeakCogSpurConfig>>prepareForGeneration (in category 'source generation') -----
- prepareForGeneration
- 	^ self prepareForCogGeneration!

Item was removed:
- ----- Method: Win32x86NewspeakCogV3Config>>prepareForGeneration (in category 'source generation') -----
- prepareForGeneration
- 	^ self prepareForCogGeneration!

Item was added:
+ ----- Method: Win32x86NewspeakSistaSpurConfig>>cogitClass (in category 'source generation') -----
+ cogitClass
+ 	^SistaStackToRegisterMappingCogit
+ !

Item was changed:
  ----- Method: Win32x86NewspeakSistaSpurConfig>>interpreterClass (in category 'source generation') -----
  interpreterClass
+ 	^ CoInterpreter
+ !
- 	"answer an interpreter class for VM source code generation"
- 	^ StackInterpreter!

Item was removed:
- ----- Method: Win32x86NewspeakSistaSpurConfig>>prepareForGeneration (in category 'source generation') -----
- prepareForGeneration
- 	^ self prepareForStackVMGeneration!

Item was added:
+ ----- Method: Win32x86NewspeakSistaV3Config>>cogitClass (in category 'source generation') -----
+ cogitClass
+ 	^SistaStackToRegisterMappingCogit
+ !

Item was changed:
  ----- Method: Win32x86NewspeakSistaV3Config>>interpreterClass (in category 'source generation') -----
  interpreterClass
+ 	^ CoInterpreter
+ !
- 	"answer an interpreter class for VM source code generation"
- 	^ StackInterpreter!

Item was removed:
- ----- Method: Win32x86NewspeakSistaV3Config>>prepareForGeneration (in category 'source generation') -----
- prepareForGeneration
- 	^ self prepareForStackVMGeneration!

Item was added:
+ ----- Method: Win32x86NewspeakStackSpurConfig>>cogitClass (in category 'source generation') -----
+ cogitClass
+ 	"answer a class for machine code generation or nil"
+ 	
+ 	^ StackToRegisterMappingCogit !

Item was removed:
- ----- Method: Win32x86NewspeakStackSpurConfig>>prepareForGeneration (in category 'source generation') -----
- prepareForGeneration
- 	^ self prepareForStackVMGeneration!

Item was added:
+ ----- Method: Win32x86NewspeakStackV3Config>>cogitClass (in category 'source generation') -----
+ cogitClass
+ 	^ StackToRegisterMappingCogit 
+ !

Item was removed:
- ----- Method: Win32x86NewspeakStackV3Config>>prepareForGeneration (in category 'source generation') -----
- prepareForGeneration
- 	^ self prepareForStackVMGeneration!

Item was removed:
- ----- Method: Win32x86SqueakCogSpurConfig>>prepareForGeneration (in category 'source generation') -----
- prepareForGeneration
- 	^ self prepareForCogGeneration!

Item was removed:
- ----- Method: Win32x86SqueakCogV3Config>>prepareForGeneration (in category 'source generation') -----
- prepareForGeneration
- 	^ self prepareForCogGeneration!

Item was added:
+ ----- Method: Win32x86SqueakCogV3DebugConfigz>>cogitClass (in category 'source generation') -----
+ cogitClass
+ 	^ StackToRegisterMappingCogit 
+ !

Item was added:
+ ----- Method: Win32x86SqueakCogV3DebugConfigz>>interpreterClass (in category 'source generation') -----
+ interpreterClass
+ 	^ CoInterpreter
+ !

Item was added:
+ ----- Method: Win32x86SqueakCogV3MultiThreadedConfigz>>cogitClass (in category 'source generation') -----
+ cogitClass
+ 	^ StackToRegisterMappingCogit 
+ !

Item was changed:
  ----- Method: Win32x86SqueakCogV3MultiThreadedConfigz>>executableName (in category 'accessing') -----
  executableName
+ 	^ self vmCogExecutableName!
- 	^ 'CogMTVM'!

Item was added:
+ ----- Method: Win32x86SqueakSistaSpurConfig>>cogitClass (in category 'source generation') -----
+ cogitClass
+ 	^SistaStackToRegisterMappingCogit
+ !

Item was changed:
  ----- Method: Win32x86SqueakSistaSpurConfig>>interpreterClass (in category 'source generation') -----
  interpreterClass
+ 	^ CoInterpreter
+ !
- 	"answer an interpreter class for VM source code generation"
- 	^ StackInterpreter!

Item was removed:
- ----- Method: Win32x86SqueakSistaSpurConfig>>prepareForGeneration (in category 'source generation') -----
- prepareForGeneration
- 	^ self prepareForStackVMGeneration!

Item was added:
+ ----- Method: Win32x86SqueakSistaV3Config>>cogitClass (in category 'source generation') -----
+ cogitClass
+ 	^SistaStackToRegisterMappingCogit
+ !

Item was changed:
  ----- Method: Win32x86SqueakSistaV3Config>>interpreterClass (in category 'source generation') -----
  interpreterClass
+ 	^ CoInterpreter
+ !
- 	"answer an interpreter class for VM source code generation"
- 	^ StackInterpreter!

Item was removed:
- ----- Method: Win32x86SqueakSistaV3Config>>prepareForGeneration (in category 'source generation') -----
- prepareForGeneration
- 	^ self prepareForStackVMGeneration!

Item was added:
+ ----- Method: Win32x86SqueakStackSpurConfig>>cogitClass (in category 'source generation') -----
+ cogitClass
+ 	^ StackToRegisterMappingCogit 
+ !

Item was changed:
  ----- Method: Win32x86SqueakStackSpurConfig>>interpreterClass (in category 'source generation') -----
  interpreterClass
- 	"answer an interpreter class for VM source code generation"
  	^ StackInterpreter!

Item was removed:
- ----- Method: Win32x86SqueakStackSpurConfig>>prepareForGeneration (in category 'source generation') -----
- prepareForGeneration
- 	^ self prepareForStackVMGeneration!

Item was added:
+ ----- Method: Win32x86SqueakStackV3Config>>cogitClass (in category 'source generation') -----
+ cogitClass
+ 	^ StackToRegisterMappingCogit 
+ !

Item was changed:
  ----- Method: Win32x86SqueakStackV3Config>>interpreterClass (in category 'source generation') -----
  interpreterClass
- 	"answer an interpreter class for VM source code generation"
  	^ StackInterpreter!

Item was removed:
- ----- Method: Win32x86SqueakStackV3Config>>prepareForGeneration (in category 'source generation') -----
- prepareForGeneration
- 	^ self prepareForStackVMGeneration!



More information about the Vm-dev mailing list