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

commits at source.squeak.org commits at source.squeak.org
Fri Jun 6 22:31:26 UTC 2014


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

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

Name: CMakeVMMakerSqueak-tty.32
Author: tty
Time: 6 June 2014, 6:31:24.735 pm
UUID: 4cdef0a2-67c3-42fe-87c3-44b96c1df4c6
Ancestors: CMakeVMMakerSqueak-tty.31

Refactoring sweep. much more to go. 

Added infrastructure for Builders to report what targets they support and what kind of builds they support.

stuff like 
SqueakAndroidBuilder availableTargets etc.

Removed old Traits from first port from Pharo and added a new Trait. Installed this trait at the topmost class of the Squeak heirarchy which is inter-twined with the existing pharo hierarchy. Ugly, but not too ugly and supports decision not to fork existing work. This lets me enforce a pseudo-abstract class discipline. 

Probably two more days coding to get this to production.

=============== Diff against CMakeVMMakerSqueak-tty.31 ===============

Item was removed:
- TSqueakStackUnixConfig classTrait
- 	uses: TSqueakCPlatformConfig classTrait!

Item was added:
+ CPlatformConfig subclass: #Linux32x86Config
+ 	uses: TCPlatformConfigForSqueak
+ 	instanceVariableNames: ''
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'CMakeVMMakerSqueak-Linux32x86'!
+ Linux32x86Config class
+ 	uses: TCPlatformConfigForSqueak classTrait
+ 	instanceVariableNames: ''!

Item was changed:
+ Linux32x86Config subclass: #Linux32x86NewspeakCogV3Config
- CPlatformConfig subclass: #Linux32x86NewspeakCogV3Config
  	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'CMakeVMMakerSqueak-Linux32x86'!

Item was changed:
+ Linux32x86Config subclass: #Linux32x86NewspeakStackV3Config
- CPlatformConfig subclass: #Linux32x86NewspeakStackV3Config
  	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'CMakeVMMakerSqueak-Linux32x86'!

Item was changed:
+ Linux32x86Config subclass: #Linux32x86SqueakCogSpurConfig
- CPlatformConfig subclass: #Linux32x86SqueakCogSpurConfig
  	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'CMakeVMMakerSqueak-Linux32x86'!

Item was changed:
  CogFamilyUnixConfig subclass: #Linux32x86SqueakCogV3Config
+ 	uses: TCPlatformConfigForSqueak
  	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'CMakeVMMakerSqueak-Linux32x86'!
  
  !Linux32x86SqueakCogV3Config commentStamp: 'tty 6/2/2014 17:20' prior: 0!
  Base and concrete configuration for building a CogVM on Unix platform(s).
  
  Usage: 
  SqueakCogUnixConfig generateWithSources
  or
  SqueakCogUnixConfig generate   "if VMMaker sources already there"
  
  
  Fore more information, check the class comments of all the superclasses.
  !
+ Linux32x86SqueakCogV3Config class
+ 	uses: TCPlatformConfigForSqueak classTrait
+ 	instanceVariableNames: ''!

Item was added:
+ ----- Method: Linux32x86SqueakCogV3Config class>>availableBuilds (in category 'as yet unclassified') -----
+ availableBuilds
+ 	"Answer a subset of SqueakCMakeVMMakerAbstractBuilder allBuildConfigurations"
+ 	self flag:'tty'. "This really should be at the top of the inheritence tree, but that resides in Pharo's code. Please refactor me"
+ 	self subclassResponsibility!

Item was changed:
  CPlatformConfig subclass: #Linux32x86SqueakStackSpurConfig
+ 	uses: TCPlatformConfigForSqueak
  	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'CMakeVMMakerSqueak-Linux32x86'!
+ Linux32x86SqueakStackSpurConfig class
+ 	uses: TCPlatformConfigForSqueak classTrait
+ 	instanceVariableNames: ''!

Item was added:
+ ----- Method: Linux32x86SqueakStackSpurConfig class>>availableBuilds (in category 'as yet unclassified') -----
+ availableBuilds
+ 	"Answer a subset of SqueakCMakeVMMakerAbstractBuilder allBuildConfigurations"
+ 	self flag:'tty'. "This really should be at the top of the inheritence tree, but that resides in Pharo's code. Please refactor me"
+ 	self subclassResponsibility!

Item was changed:
  StackUnixConfig subclass: #Linux32x86SqueakStackV3Config
+ 	uses: TCPlatformConfigForSqueak
- 	uses: TSqueakStackUnixConfig - {#externalPlugins. #internalPlugins}
  	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'CMakeVMMakerSqueak-Linux32x86'!
  
  !Linux32x86SqueakStackV3Config commentStamp: 'tty 5/16/2014 17:13' prior: 0!
  I configure a StackVM for Linux. 
  
  My method protocol 'squeak compatibility' contains all the methods in pharo's CMakeVMMaker that I must implement differently/override. 
  
  I use Trait TSqueckStackUnixConfig which forces me and my subclasses to implement pharo CMakeVMMaker methods.
  
  My subclasses, implement them by super calls back to me. Yes, it is not efficient, but in this case, subclassing is not possible due to existing pharo heirarchy
  
  
  
  
  
  !
  Linux32x86SqueakStackV3Config class
+ 	uses: TCPlatformConfigForSqueak classTrait
- 	uses: TSqueakStackUnixConfig classTrait
  	instanceVariableNames: ''!

Item was added:
+ ----- Method: Linux32x86SqueakStackV3Config class>>availableBuilds (in category 'as yet unclassified') -----
+ availableBuilds
+ 	"Answer a subset of SqueakCMakeVMMakerAbstractBuilder allBuildConfigurations"
+ 	self subclassResponsibility!

Item was changed:
  Linux32x86SqueakStackV3Config subclass: #Linux32x86SqueakStackV3SlackwareConfig
+ 	uses: TCPlatformConfigForSqueak
- 	uses: TSqueakStackUnixConfig - {#externalPlugins. #internalPlugins}
  	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'CMakeVMMakerSqueak-Linuxx86_64-32Compatibility'!
  
  !Linux32x86SqueakStackV3SlackwareConfig commentStamp: 'tty 5/21/2014 11:04' prior: 0!
  A SqueakStackUnix64w32CompatLibsSlackwareConfig is a configuration for CMake on a 64 bit Slackware linux with 32 bit compat libs and includes linking to GL. 
  
  
  
  Usage:
  SqueakStackVMBuilder 	buildSlackwareUnix64w32Libs
  Or:
  SqueakStackUnix64w32CompatLibsSlackwareConfig generateWithSources.
  Or:
  SqueakStackUnix64w32CompatLibsSlackwareConfig generate
  
  !
  Linux32x86SqueakStackV3SlackwareConfig class
+ 	uses: TCPlatformConfigForSqueak classTrait
- 	uses: TSqueakStackUnixConfig classTrait
  	instanceVariableNames: ''!

Item was changed:
  Linux32x86SqueakStackV3SlackwareConfig subclass: #Linux32x86SqueakStackV3SlackwareNoGLConfig
+ 	uses: AnObsoleteTSqueakStackUnixConfig - {#externalPlugins. #internalPlugins}
- 	uses: TSqueakStackUnixConfig - {#externalPlugins. #internalPlugins}
  	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'CMakeVMMakerSqueak-Linuxx86_64-32Compatibility'!
  
  !Linux32x86SqueakStackV3SlackwareNoGLConfig commentStamp: 'tty 5/21/2014 11:05' prior: 0!
  Usage:
  SqueakStackVMBuilder 	buildSlackwareUnix64w32Libs
  Or:
  SqueakStackUnix64w32CompatLibsSlackwareNoGLConfig generateWithSources.
  Or:
  SqueakStackUnix64w32CompatLibsSlackwareNoGLConfig generate
  !
  Linux32x86SqueakStackV3SlackwareNoGLConfig class
+ 	uses: AnObsoleteTSqueakStackUnixConfig classTrait
- 	uses: TSqueakStackUnixConfig classTrait
  	instanceVariableNames: ''!

Item was changed:
  Linux32x86SqueakCogV3Config subclass: #Linux64SqueakCogSpur
+ 	uses: TCPlatformConfigForSqueak
  	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'CMakeVMMakerSqueak-Linuxx86_64'!
  
  !Linux64SqueakCogSpur commentStamp: 'tty 6/5/2014 12:10' prior: 0!
  Linux64SqueakCogSpur has not been coded yet.
  
  I am a placeholder for the upcoming Spur release in 2014.
  !
+ Linux64SqueakCogSpur class
+ 	uses: TCPlatformConfigForSqueak classTrait
+ 	instanceVariableNames: ''!

Item was added:
+ SqueakCMakeVMMakerAbstractBuilder subclass: #SqueakAndroidBuilder
+ 	instanceVariableNames: ''
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'CMakeVMMakerSqueak-Builder'!
+ 
+ !SqueakAndroidBuilder commentStamp: '<historical>' prior: 0!
+ I serve as a facade to ease building Cog VM with CMakeVMMakerSqueak configs
+ 
+ !

Item was added:
+ ----- Method: SqueakAndroidBuilder class>>availableBuildTypesForTarget: (in category 'documentation') -----
+ availableBuildTypesForTarget: aSymbol
+ 	[
+ 	((Smalltalk at: aSymbol)  category) = 'CMakeVMMakerSqueak-Android'
+ 		ifTrue:[	^super availableBuildsTypesForTarget: aSymbol inCategory: ((Smalltalk at: aSymbol)  category).]
+ 		ifFalse:[self inform: (self userErrorInvalidTarget: aSymbol)]
+ 	] ifError:[self inform: (self userErrorInvalidTarget: aSymbol)].
+ 	^nil.!

Item was added:
+ ----- Method: SqueakAndroidBuilder class>>availableTargets (in category 'documentation') -----
+ availableTargets
+ 	^super availableTargets: 'CMakeVMMakerSqueak-Android'!

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

Item was added:
+ ----- Method: SqueakAndroidStackEvtConfig class>>availableBuilds (in category 'as yet unclassified') -----
+ availableBuilds
+ 	^SqueakCMakeVMMakerAbstractBuilder noBuildConfigurations!

Item was added:
+ ----- Method: SqueakAndroidStackEvtConfig>>buildDirName (in category 'squeak compatibility') -----
+ buildDirName
+ 	^'do not build. see class comment'!

Item was changed:
  Linux32x86SqueakCogV3Config subclass: #SqueakBSDCogV3Config
- 	uses: TSqueakStackUnixConfig - {#externalPlugins. #internalPlugins}
  	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'CMakeVMMakerSqueak-BSD32x86'!
- 
- !SqueakBSDCogV3Config commentStamp: 'tty 5/21/2014 12:24' prior: 0!
- I am a configuration for Cog on BSD.
- 
- 
- 
- 
- Usage:
- SqueakCogFreeBSDConfig generateWithSources
- or:
- SqueakCogFreeBSDConfig generate
- 
- !
- SqueakBSDCogV3Config class
- 	uses: TSqueakStackUnixConfig classTrait
- 	instanceVariableNames: ''!

Item was changed:
  ----- Method: SqueakBSDCogV3Config>>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 changed:
  ----- Method: SqueakBSDCogV3Config>>buildDir (in category 'as yet unclassified') -----
  buildDir
  	^ buildDir ifNil: [ buildDir := ( self topDir / self buildDirName) assureExistence].!

Item was changed:
  ----- Method: SqueakBSDCogV3Config>>buildDirName (in category 'as yet unclassified') -----
  buildDirName
  	self subclassResponsibility!

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

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

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

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

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

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

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

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

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

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

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

Item was changed:
+ ----- Method: SqueakBSDCogV3Config>>write:toFile: (in category 'as yet unclassified') -----
- ----- Method: SqueakBSDCogV3Config>>write:toFile: (in category 'accessing') -----
  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:
+ SqueakCMakeVMMakerAbstractBuilder subclass: #SqueakBSDX86Builder
- Object subclass: #SqueakBSDX86Builder
  	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'CMakeVMMakerSqueak-Builder'!
  
  !SqueakBSDX86Builder commentStamp: '<historical>' prior: 0!
  I serve as a facade to ease building Cog VM with CMakeVMMakerSqueak configs
  
  !

Item was added:
+ ----- Method: SqueakBSDX86Builder class>>availableBuildTypesForTarget: (in category 'documentation') -----
+ availableBuildTypesForTarget: aSymbol
+ 	[
+ 	((Smalltalk at: aSymbol)  category) = 'CMakeVMMakerSqueak-BSD32x86'
+ 		ifTrue:[	^super availableBuildsTypesForTarget: aSymbol inCategory: ((Smalltalk at: aSymbol)  category).]
+ 		ifFalse:[self inform: (self userErrorInvalidTarget: aSymbol)]
+ 	] ifError:[self inform: (self userErrorInvalidTarget: aSymbol)].
+ 	^nil.!

Item was added:
+ ----- Method: SqueakBSDX86Builder class>>availableTargets (in category 'documentation') -----
+ availableTargets
+ 	^super availableTargets: 'CMakeVMMakerSqueak-BSD32x86'!

Item was removed:
- ----- Method: SqueakBSDX86Builder class>>buildBSD (in category 'building') -----
- buildBSD
- 	^ self new buildBSD!

Item was removed:
- ----- Method: SqueakBSDX86Builder class>>buildDirNameForBSD (in category 'documentation') -----
- buildDirNameForBSD
- 	^ self new buildDirNameForBSD!

Item was removed:
- ----- Method: SqueakBSDX86Builder>>buildBSD (in category 'building') -----
- buildBSD
- 	SqueakFreeBSDCogV3Config new  
- 		addExternalPlugins: #(  FT2Plugin );
- 		addInternalPlugins: #( UnixOSProcessPlugin );
- 		generateSources; generate.
- !

Item was removed:
- ----- Method: SqueakBSDX86Builder>>buildDirNameForBSD (in category 'building') -----
- buildDirNameForBSD
- 	^SqueakFreeBSDCogV3Config new  buildDirName
- !

Item was removed:
- ----- Method: SqueakBSDX86Builder>>initialize (in category 'initialization') -----
- initialize
- 
- 	"a stupid temporary hack to workaround initialization problems"
- 
- 	Cogit allSubclassesDo: [ :each | each initializeWithOptions: (VMMaker new instVarNamed: 'optionsDictionary') ]!

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

Item was added:
+ ----- Method: SqueakCMakeVMMakerAbstractBuilder class>>allBuildConfigurations (in category 'as yet unclassified') -----
+ allBuildConfigurations
+ 	^#(#assert #assertWithHeartbeatTimer #debug #debugWithHeartbeatTimer #debugMultiThreadedFFI #release #releaseHeartbeatTimer #releaseMultiThreadedFFI)!

Item was added:
+ ----- Method: SqueakCMakeVMMakerAbstractBuilder class>>availableBuildTypesForTarget: (in category 'as yet unclassified') -----
+ availableBuildTypesForTarget: aSymbol
+ 	self subclassResponsibility.
+ 
+ 
+ !

Item was added:
+ ----- Method: SqueakCMakeVMMakerAbstractBuilder class>>availableBuildsTypesForTarget:inCategory: (in category 'as yet unclassified') -----
+ availableBuildsTypesForTarget: aSymbol inCategory: aCategoryName
+ 	|d |
+ 	d:=(self configurationDictionary:aCategoryName) at: aSymbol ifAbsent:[^SqueakCMakeVMMakerAbstractBuilder noBuildConfigurations].
+ 	^d value
+ 
+ 
+ 
+ !

Item was added:
+ ----- Method: SqueakCMakeVMMakerAbstractBuilder class>>availableTargets: (in category 'as yet unclassified') -----
+ availableTargets: aCategoryName
+ 
+ 	^((self configurationDictionary:aCategoryName) keys asSortedCollection) sort
+ 
+ !

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

Item was added:
+ ----- Method: SqueakCMakeVMMakerAbstractBuilder class>>noBuildConfigurations (in category 'as yet unclassified') -----
+ noBuildConfigurations
+ 	^#(#noBuildsImplementedForThisConfiguration)!

Item was added:
+ ----- Method: SqueakCMakeVMMakerAbstractBuilder class>>userErrorInvalidTarget: (in category 'as yet unclassified') -----
+ userErrorInvalidTarget: aSymbol
+ 	^'I cannot build for this target', aSymbol asString.!

Item was added:
+ ----- Method: SqueakCMakeVMMakerAbstractBuilder>>initialize (in category 'initialization') -----
+ initialize
+ 
+ 	"a stupid temporary hack to workaround initialization problems"
+ 
+ 	Cogit allSubclassesDo: [ :each | each initializeWithOptions: (VMMaker new instVarNamed: 'optionsDictionary') ]!

Item was added:
+ CPlatformConfig subclass: #SqueakIA32BochsConfig
+ 	uses: TCPlatformConfigForSqueak
+ 	instanceVariableNames: ''
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'CMakeVMMakerSqueak-IA32-Bochs'!
+ SqueakIA32BochsConfig class
+ 	uses: TCPlatformConfigForSqueak classTrait
+ 	instanceVariableNames: ''!

Item was changed:
+ SqueakIA32BochsConfig subclass: #SqueakIA32BochsLinuxConfig
- CPlatformConfig subclass: #SqueakIA32BochsLinuxConfig
  	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'CMakeVMMakerSqueak-IA32-Bochs'!

Item was added:
+ ----- Method: SqueakIA32BochsLinuxConfig class>>availableBuilds (in category 'as yet unclassified') -----
+ availableBuilds
+ 	^SqueakCMakeVMMakerAbstractBuilder noBuildConfigurations!

Item was changed:
+ SqueakIA32BochsConfig subclass: #SqueakIA32BochsMacOSConfig
- CPlatformConfig subclass: #SqueakIA32BochsMacOSConfig
  	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'CMakeVMMakerSqueak-IA32-Bochs'!

Item was changed:
+ SqueakIA32BochsConfig subclass: #SqueakIA32BochsMacOSXConfig
- CPlatformConfig subclass: #SqueakIA32BochsMacOSXConfig
  	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'CMakeVMMakerSqueak-IA32-Bochs'!

Item was changed:
+ SqueakIA32BochsConfig subclass: #SqueakIA32BochsWin32Config
- CPlatformConfig subclass: #SqueakIA32BochsWin32Config
  	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'CMakeVMMakerSqueak-IA32-Bochs'!

Item was added:
+ SqueakCMakeVMMakerAbstractBuilder subclass: #SqueakLinux32X86Builder
+ 	instanceVariableNames: ''
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'CMakeVMMakerSqueak-Builder'!
+ 
+ !SqueakLinux32X86Builder commentStamp: 'tty 5/23/2014 17:56' prior: 0!
+ I serve as a facade to ease building Cog VM with CMakeVMMakerSqueak configs
+ 
+ !

Item was added:
+ ----- Method: SqueakLinux32X86Builder class>>availableBuildTypesForTarget: (in category 'documentation') -----
+ availableBuildTypesForTarget: aSymbol
+ 	[
+ 	((Smalltalk at: aSymbol)  category) =  'CMakeVMMakerSqueak-Linux32x86'
+ 		ifTrue:[	^super availableBuildsTypesForTarget: aSymbol inCategory: ((Smalltalk at: aSymbol)  category).]
+ 		ifFalse:[self inform: (self userErrorInvalidTarget: aSymbol)]
+ 	] ifError:[self inform: (self userErrorInvalidTarget: aSymbol)].
+ 	^nil.!

Item was added:
+ ----- Method: SqueakLinux32X86Builder class>>availableTargets (in category 'documentation') -----
+ availableTargets
+ 	^super availableTargets: 'CMakeVMMakerSqueak-Linux32x86'!

Item was changed:
+ SqueakCMakeVMMakerAbstractBuilder subclass: #SqueakLinuxARMBuilder
- Object subclass: #SqueakLinuxARMBuilder
  	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'CMakeVMMakerSqueak-Builder'!
  
  !SqueakLinuxARMBuilder commentStamp: '<historical>' prior: 0!
  I serve as a facade to ease building Cog VM with CMakeVMMakerSqueak configs
  
  !

Item was added:
+ ----- Method: SqueakLinuxARMBuilder class>>availableBuildTypesForTarget: (in category 'documentation') -----
+ availableBuildTypesForTarget: aSymbol
+ 	[
+ 	((Smalltalk at: aSymbol)  category) =  'CMakeVMMakerSqueak-Linux32ARMv6'
+ 		ifTrue:[	^super availableBuildsTypesForTarget: aSymbol inCategory: ((Smalltalk at: aSymbol)  category).]
+ 		ifFalse:[self inform: (self userErrorInvalidTarget: aSymbol). ]
+ 	] ifError:[self inform: (self userErrorInvalidTarget: aSymbol)].
+ 	^nil.
+ !

Item was added:
+ ----- Method: SqueakLinuxARMBuilder class>>availableTargets (in category 'documentation') -----
+ availableTargets
+ 	^super availableTargets: 'CMakeVMMakerSqueak-Linux32ARMv6'!

Item was removed:
- ----- Method: SqueakLinuxARMBuilder class>>buildDirNameForLinux32 (in category 'documentation') -----
- buildDirNameForLinux32
- 	^ self new buildDirNameForLinux32!

Item was removed:
- ----- Method: SqueakLinuxARMBuilder class>>buildLinux32 (in category 'building') -----
- buildLinux32
- 	^ self new buildLinux32!

Item was removed:
- ----- Method: SqueakLinuxARMBuilder>>buildDirNameForBSD32 (in category 'documentation') -----
- buildDirNameForBSD32
- 	^SqueakFreeBSDCogV3Config new  buildDirName
- !

Item was removed:
- ----- Method: SqueakLinuxARMBuilder>>buildStackV3CrossRaspbian (in category 'building') -----
- buildStackV3CrossRaspbian 
- 
- 	Linux32ARMv6StackV3CrossRaspbianConfig new  
- 		generateForRelease;
- 		"generateForDebug;"
- 		addExternalPlugins: #(  FT2Plugin );
- 		addInternalPlugins: #( UnixOSProcessPlugin );
- 		generateSources; generate.
- !

Item was removed:
- ----- Method: SqueakLinuxARMBuilder>>initialize (in category 'initialization') -----
- initialize
- 
- 	"a stupid temporary hack to workaround initialization problems"
- 
- 	Cogit allSubclassesDo: [ :each | each initializeWithOptions: (VMMaker new instVarNamed: 'optionsDictionary') ]!

Item was removed:
- Object subclass: #SqueakLinuxX86Builder
- 	instanceVariableNames: ''
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'CMakeVMMakerSqueak-Builder'!
- 
- !SqueakLinuxX86Builder commentStamp: 'tty 5/23/2014 17:56' prior: 0!
- I serve as a facade to ease building Cog VM with CMakeVMMakerSqueak configs
- 
- !

Item was removed:
- ----- Method: SqueakLinuxX86Builder class>>buildDirNameForLinux32 (in category 'documentation') -----
- buildDirNameForLinux32
- 	^ self new buildDirNameForLinux32!

Item was removed:
- ----- Method: SqueakLinuxX86Builder class>>buildLinux32 (in category 'building') -----
- buildLinux32
- 	^ self new buildLinux32!

Item was removed:
- ----- Method: SqueakLinuxX86Builder>>buildBSD32 (in category 'building') -----
- buildBSD32 
- 
- 	SqueakFreeBSDCogV3Config new  
- 		generateForRelease;
- 		"generateForDebug;"
- 		addExternalPlugins: #(  FT2Plugin );
- 		addInternalPlugins: #( UnixOSProcessPlugin );
- 		generateSources; generate.
- !

Item was removed:
- ----- Method: SqueakLinuxX86Builder>>buildDirNameForBSD32 (in category 'documentation') -----
- buildDirNameForBSD32
- 	^SqueakFreeBSDCogV3Config new  buildDirName
- !

Item was removed:
- ----- Method: SqueakLinuxX86Builder>>initialize (in category 'initialization') -----
- initialize
- 
- 	"a stupid temporary hack to workaround initialization problems"
- 
- 	Cogit allSubclassesDo: [ :each | each initializeWithOptions: (VMMaker new instVarNamed: 'optionsDictionary') ]!

Item was added:
+ CPlatformConfig subclass: #SqueakMacOSConfig
+ 	uses: TCPlatformConfigForSqueak
+ 	instanceVariableNames: ''
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'CMakeVMMakerSqueak-MacOS'!
+ SqueakMacOSConfig class
+ 	uses: TCPlatformConfigForSqueak classTrait
+ 	instanceVariableNames: ''!

Item was added:
+ ----- Method: SqueakMacOSConfig class>>availableBuilds (in category 'as yet unclassified') -----
+ availableBuilds
+ 	"Answer a subset of SqueakCMakeVMMakerAbstractBuilder allBuildConfigurations"
+ 	self subclassResponsibility!

Item was changed:
+ SqueakMacOSConfig subclass: #SqueakMacOSV3Config
- CPlatformConfig subclass: #SqueakMacOSV3Config
  	instanceVariableNames: 'resourcesDir'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'CMakeVMMakerSqueak-MacOS'!
  
  !SqueakMacOSV3Config commentStamp: '<historical>' prior: 0!
  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).
  
  
  Fore more information, check the class comments of all the superclasses.
  !

Item was changed:
  CPlatformConfig subclass: #SqueakSunOS32x8664CogConfig
+ 	uses: TCPlatformConfigForSqueak
  	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'CMakeVMMakerSqueak-SunOS32x86_64'!
+ SqueakSunOS32x8664CogConfig class
+ 	uses: TCPlatformConfigForSqueak classTrait
+ 	instanceVariableNames: ''!

Item was changed:
  CPlatformConfig subclass: #SqueakSunOS32x86CogConfig
+ 	uses: TCPlatformConfigForSqueak
  	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'CMakeVMMakerSqueak-SunOS32x86'!
+ SqueakSunOS32x86CogConfig class
+ 	uses: TCPlatformConfigForSqueak classTrait
+ 	instanceVariableNames: ''!

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

Item was added:
+ Trait named: #TCPlatformConfigForSqueak
+ 	uses: {}
+ 	category: 'CMakeVMMakerSqueak'!
+ 
+ !TCPlatformConfigForSqueak commentStamp: 'tty 6/6/2014 16:01' prior: 0!
+ A TSqueakCPlatformConfig provides a template of methods which must be customized for Squeak compatibility with  pharo CMakeVMMaker classes.
+ 
+ I exist because tty does not have (and, should not have) permission to modify  to the existing inheritence tree in the pharo CMakeVMMaker categories.
+ 
+ 
+ 
+ 
+ 
+ !

Item was added:
+ ----- Method: TCPlatformConfigForSqueak class>>availableBuilds (in category 'accessing') -----
+ availableBuilds
+ 	"
+ 	 ^SqueakCMakeVMMakerAbstractBuilder noBuildConfigurations.
+ 	  ^SqueakCMakeVMMakerAbstractBuilder allBuildConfigurations.
+ 	 or roll your own.
+ 	"
+ 	self required!

Item was added:
+ ----- Method: TCPlatformConfigForSqueak class>>licenseTemplate (in category 'accessing') -----
+ licenseTemplate
+ 	^'Squeak {1} license information
+ ==============================
+ 
+ About Squeak
+ -----------
+ Squeak is a modern, open source, full-featured implementation of the powerful Smalltalk programming language and environment. Squeak is highly-portable, running on almost any platform you could name and you can really truly write once run anywhere.  Squeak is the vehicle for a wide range of projects from multimedia applications and educational platforms to commercial web application development.
+ 
+ LIcense
+ Note: The current release of Squeak is a combination of source code originating from it''s origins at Apple which Apple agreed to license under the Apache license and more recent contributions licensed under the MIT license. The vast majority of the code is under the MIT license.
+ MIT License
+ 
+ Copyright (c) The individual, corporate, and institutional contributors who have collectively contributed elements to this software ("The Squeak Community"), 1996-2010 All rights reserved.
+ 
+ Permission is hereby granted, free of charge, to any person obtaining a copy of this software and associated documentation files (the "Software"), to deal in the Software without restriction, including without limitation the rights to use, copy, modify, merge, publish, distribute, sublicense, and/or sell copies of the Software, and to permit persons to whom the Software is furnished to do so, subject to the following conditions:
+ 
+ The above copyright notice and this permission notice shall be included in all copies or substantial portions of the Software.
+ 
+ THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE.
+ Portions of Squeak are covered by the following license:
+ Apache License, Version 2.0
+ 
+ Copyright (c) Xerox Corp. 1981, 1982 All rights reserved. Copyright (c) Apple Computer, Inc. 1985-1996 All rights reserved.
+ 
+ Licensed under the Apache License, Version 2.0 (the "License"); you may not use this file except in compliance with the License. You may obtain a copy of the License at
+ 
+ http://www.apache.org/licenses/LICENSE-2.0
+ 
+ Unless required by applicable law or agreed to in writing, software distributed under the License is distributed on an "AS IS" BASIS, WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied. See the License for the specific language governing permissions and limitations under the License.
+ 
+ 
+ About Cog
+ ---------
+ 
+ Cog is a virtual machine designed for Smalltalk and other similar dynamic languages.  Cog builds on the
+ Squeak virtual machine adding a stack-to-register-mapping just-in-time compiler, aggressive in-line message
+ cacheing and effective optimization of Smalltalk?s first-class activation records.  Cog is the virtual machine
+ underlying Teleplace''s Croquet-based enterprise virtual collaboration spaces software, the fastest virtual
+ machine for Squeak, and for Gilad Bracha''s Newspeak modular language inspired by Beta and Smalltalk.  
+ Like the original Squeak VM, Cog is implemented and developed in Smalltalk, and translated into a lower-level
+ language to produce the production VM.  Being a Smalltalk program it is a delight to develop.  Cog is
+ available under the MIT open source license and is unencumbered for commercial deployment.
+ 
+ Cog''s performance relative to the existing Squeak interpreter varies, depending on the benchmark chosen.
+ As of early-2011, the Cog JIT uses strong inline cacheing techniques and stack-to-register mapping that
+ results in a register-based calling convention for low-arity methods.  Due to the complexity of the Squeak
+ object representation it has a limited set of primitives implemented in machine code that, for example,
+ exclude object allocation.  Performance of the early-2011 JIT for the nbody, binarytrees and chameneos
+ redux benchmarks from the computer language shootout is in the range of 4 to 6 times faster than the
+ interpreter.
+ '!

Item was added:
+ ----- Method: TCPlatformConfigForSqueak class>>pluginsTemplate (in category 'accessing') -----
+ pluginsTemplate
+ 	^'{4} {1} ships with this plugins already built:
+ 		
+ Internal: 
+ =========
+ {2}
+ 
+ External: 
+ =========
+ {3}
+ 
+ '!

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

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

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

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

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

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

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

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

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

Item was added:
+ ----- Method: TCPlatformConfigForSqueak>>write:toFile: (in category 'squeak compatibility') -----
+ write: aContents toFile: aFileName
+ 	self required!

Item was removed:
- Trait named: #TSqueakCPlatformConfig
- 	uses: {}
- 	category: 'CMakeVMMakerSqueak'!
- 
- !TSqueakCPlatformConfig commentStamp: 'tty 5/16/2014 16:03' prior: 0!
- A TSqueakCPlatformConfig provides a template of methods which must be customized for Squeak compatibility with  pharo CMakeVMMaker classes.
- 
- Instance Variables
- !

Item was removed:
- ----- Method: TSqueakCPlatformConfig class>>licenseTemplate (in category 'accessing') -----
- licenseTemplate
- 	^'Squeak {1} license information
- ==============================
- 
- About Squeak
- -----------
- Squeak is a modern, open source, full-featured implementation of the powerful Smalltalk programming language and environment. Squeak is highly-portable, running on almost any platform you could name and you can really truly write once run anywhere.  Squeak is the vehicle for a wide range of projects from multimedia applications and educational platforms to commercial web application development.
- 
- LIcense
- Note: The current release of Squeak is a combination of source code originating from it''s origins at Apple which Apple agreed to license under the Apache license and more recent contributions licensed under the MIT license. The vast majority of the code is under the MIT license.
- MIT License
- 
- Copyright (c) The individual, corporate, and institutional contributors who have collectively contributed elements to this software ("The Squeak Community"), 1996-2010 All rights reserved.
- 
- Permission is hereby granted, free of charge, to any person obtaining a copy of this software and associated documentation files (the "Software"), to deal in the Software without restriction, including without limitation the rights to use, copy, modify, merge, publish, distribute, sublicense, and/or sell copies of the Software, and to permit persons to whom the Software is furnished to do so, subject to the following conditions:
- 
- The above copyright notice and this permission notice shall be included in all copies or substantial portions of the Software.
- 
- THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE.
- Portions of Squeak are covered by the following license:
- Apache License, Version 2.0
- 
- Copyright (c) Xerox Corp. 1981, 1982 All rights reserved. Copyright (c) Apple Computer, Inc. 1985-1996 All rights reserved.
- 
- Licensed under the Apache License, Version 2.0 (the "License"); you may not use this file except in compliance with the License. You may obtain a copy of the License at
- 
- http://www.apache.org/licenses/LICENSE-2.0
- 
- Unless required by applicable law or agreed to in writing, software distributed under the License is distributed on an "AS IS" BASIS, WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied. See the License for the specific language governing permissions and limitations under the License.
- 
- 
- About Cog
- ---------
- 
- Cog is a virtual machine designed for Smalltalk and other similar dynamic languages.  Cog builds on the
- Squeak virtual machine adding a stack-to-register-mapping just-in-time compiler, aggressive in-line message
- cacheing and effective optimization of Smalltalk?s first-class activation records.  Cog is the virtual machine
- underlying Teleplace''s Croquet-based enterprise virtual collaboration spaces software, the fastest virtual
- machine for Squeak, and for Gilad Bracha''s Newspeak modular language inspired by Beta and Smalltalk.  
- Like the original Squeak VM, Cog is implemented and developed in Smalltalk, and translated into a lower-level
- language to produce the production VM.  Being a Smalltalk program it is a delight to develop.  Cog is
- available under the MIT open source license and is unencumbered for commercial deployment.
- 
- Cog''s performance relative to the existing Squeak interpreter varies, depending on the benchmark chosen.
- As of early-2011, the Cog JIT uses strong inline cacheing techniques and stack-to-register mapping that
- results in a register-based calling convention for low-arity methods.  Due to the complexity of the Squeak
- object representation it has a limited set of primitives implemented in machine code that, for example,
- exclude object allocation.  Performance of the early-2011 JIT for the nbody, binarytrees and chameneos
- redux benchmarks from the computer language shootout is in the range of 4 to 6 times faster than the
- interpreter.
- '!

Item was removed:
- ----- Method: TSqueakCPlatformConfig class>>pluginsTemplate (in category 'accessing') -----
- pluginsTemplate
- 	^'{4} {1} ships with this plugins already built:
- 		
- Internal: 
- =========
- {2}
- 
- External: 
- =========
- {3}
- 
- '!

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

Item was removed:
- ----- Method: TSqueakCPlatformConfig>>buildDirName (in category 'squeak compatibility') -----
- buildDirName
- 	self required!

Item was removed:
- ----- Method: TSqueakCPlatformConfig>>compilerFlags (in category 'squeak compatibility') -----
- compilerFlags
- 	self required!

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

Item was removed:
- ----- Method: TSqueakCPlatformConfig>>outputDir (in category 'squeak compatibility') -----
- outputDir
- 	self required
- 
- !

Item was removed:
- ----- Method: TSqueakCPlatformConfig>>setupDirectories: (in category 'squeak compatibility') -----
- setupDirectories:gen
- 	self required!

Item was removed:
- ----- Method: TSqueakCPlatformConfig>>srcDir (in category 'squeak compatibility') -----
- srcDir
- 	self required!

Item was removed:
- ----- Method: TSqueakCPlatformConfig>>topDir (in category 'squeak compatibility') -----
- topDir
- 	self required!

Item was removed:
- ----- Method: TSqueakCPlatformConfig>>validateSourcesPresent (in category 'squeak compatibility') -----
- validateSourcesPresent
- 	self required!

Item was removed:
- ----- Method: TSqueakCPlatformConfig>>write:toFile: (in category 'squeak compatibility') -----
- write: aContents toFile: aFileName
- 	self required!

Item was removed:
- Trait named: #TSqueakStackUnixConfig
- 	uses: TSqueakCPlatformConfig
- 	category: 'CMakeVMMakerSqueak'!
- 
- !TSqueakStackUnixConfig commentStamp: 'tty 5/16/2014 16:38' prior: 0!
- I'm a trait for Linux CMake configurations. I customise the top/src/build directories for a stack vm  build!

Item was removed:
- ----- Method: TSqueakStackUnixConfig class>>licenseTemplate (in category 'accessing') -----
- licenseTemplate
- 	^'Squeak {1} license information
- ==============================
- 
- About Squeak
- -----------
- Squeak is a modern, open source, full-featured implementation of the powerful Smalltalk programming language and environment. Squeak is highly-portable, running on almost any platform you could name and you can really truly write once run anywhere.  Squeak is the vehicle for a wide range of projects from multimedia applications and educational platforms to commercial web application development.
- 
- LIcense
- Note: The current release of Squeak is a combination of source code originating from it''s origins at Apple which Apple agreed to license under the Apache license and more recent contributions licensed under the MIT license. The vast majority of the code is under the MIT license.
- MIT License
- 
- Copyright (c) The individual, corporate, and institutional contributors who have collectively contributed elements to this software ("The Squeak Community"), 1996-2010 All rights reserved.
- 
- Permission is hereby granted, free of charge, to any person obtaining a copy of this software and associated documentation files (the "Software"), to deal in the Software without restriction, including without limitation the rights to use, copy, modify, merge, publish, distribute, sublicense, and/or sell copies of the Software, and to permit persons to whom the Software is furnished to do so, subject to the following conditions:
- 
- The above copyright notice and this permission notice shall be included in all copies or substantial portions of the Software.
- 
- THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE.
- Portions of Squeak are covered by the following license:
- Apache License, Version 2.0
- 
- Copyright (c) Xerox Corp. 1981, 1982 All rights reserved. Copyright (c) Apple Computer, Inc. 1985-1996 All rights reserved.
- 
- Licensed under the Apache License, Version 2.0 (the "License"); you may not use this file except in compliance with the License. You may obtain a copy of the License at
- 
- http://www.apache.org/licenses/LICENSE-2.0
- 
- Unless required by applicable law or agreed to in writing, software distributed under the License is distributed on an "AS IS" BASIS, WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied. See the License for the specific language governing permissions and limitations under the License.
- 
- 
- About Cog
- ---------
- 
- Cog is a virtual machine designed for Smalltalk and other similar dynamic languages.  Cog builds on the
- Squeak virtual machine adding a stack-to-register-mapping just-in-time compiler, aggressive in-line message
- cacheing and effective optimization of Smalltalk?s first-class activation records.  Cog is the virtual machine
- underlying Teleplace''s Croquet-based enterprise virtual collaboration spaces software, the fastest virtual
- machine for Squeak, and for Gilad Bracha''s Newspeak modular language inspired by Beta and Smalltalk.  
- Like the original Squeak VM, Cog is implemented and developed in Smalltalk, and translated into a lower-level
- language to produce the production VM.  Being a Smalltalk program it is a delight to develop.  Cog is
- available under the MIT open source license and is unencumbered for commercial deployment.
- 
- Cog''s performance relative to the existing Squeak interpreter varies, depending on the benchmark chosen.
- As of early-2011, the Cog JIT uses strong inline cacheing techniques and stack-to-register mapping that
- results in a register-based calling convention for low-arity methods.  Due to the complexity of the Squeak
- object representation it has a limited set of primitives implemented in machine code that, for example,
- exclude object allocation.  Performance of the early-2011 JIT for the nbody, binarytrees and chameneos
- redux benchmarks from the computer language shootout is in the range of 4 to 6 times faster than the
- interpreter.
- '!

Item was removed:
- ----- Method: TSqueakStackUnixConfig class>>pluginsTemplate (in category 'accessing') -----
- pluginsTemplate
- 	^'{4} {1} ships with this plugins already built:
- 		
- Internal: 
- =========
- {2}
- 
- External: 
- =========
- {3}
- 
- '!

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

Item was removed:
- ----- Method: TSqueakStackUnixConfig>>executableName (in category 'accessing') -----
- executableName
- 	self required!

Item was removed:
- ----- Method: TSqueakStackUnixConfig>>externalPlugins (in category 'accessing') -----
- externalPlugins
- 	self required!

Item was removed:
- ----- Method: TSqueakStackUnixConfig>>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: TSqueakStackUnixConfig>>generateLicense (in category 'public') -----
- generateLicense 
- 	self 
- 		write:  (self class licenseTemplate 
- 			format: { self version })
- 		toFile: 'LICENSE.txt'
- 	!

Item was removed:
- ----- Method: TSqueakStackUnixConfig>>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 removed:
- ----- Method: TSqueakStackUnixConfig>>internalPlugins (in category 'accessing') -----
- internalPlugins
- 	self required.!

Item was removed:
- ----- Method: TSqueakStackUnixConfig>>prepareVMMaker (in category 'squeak compatibility') -----
- prepareVMMaker
- 	self required!

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

Item was changed:
  CPlatformConfig subclass: #Win32x86NewspeakCogV3Config
+ 	uses: TCPlatformConfigForSqueak
  	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'CMakeVMMakerSqueak-Win32x86'!
+ Win32x86NewspeakCogV3Config class
+ 	uses: TCPlatformConfigForSqueak classTrait
+ 	instanceVariableNames: ''!

Item was changed:
  CPlatformConfig subclass: #Win32x86NewspeakStackV3Config
+ 	uses: TCPlatformConfigForSqueak
  	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'CMakeVMMakerSqueak-Win32x86'!
+ Win32x86NewspeakStackV3Config class
+ 	uses: TCPlatformConfigForSqueak classTrait
+ 	instanceVariableNames: ''!

Item was changed:
  CPlatformConfig subclass: #Win32x86SqueakCogSpurConfig
+ 	uses: TCPlatformConfigForSqueak
  	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'CMakeVMMakerSqueak-Win32x86'!
+ Win32x86SqueakCogSpurConfig class
+ 	uses: TCPlatformConfigForSqueak classTrait
+ 	instanceVariableNames: ''!

Item was changed:
  CPlatformConfig subclass: #Win32x86SqueakStackSpurConfig
+ 	uses: TCPlatformConfigForSqueak
  	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'CMakeVMMakerSqueak-Win32x86'!
+ Win32x86SqueakStackSpurConfig class
+ 	uses: TCPlatformConfigForSqueak classTrait
+ 	instanceVariableNames: ''!



More information about the Vm-dev mailing list