Small fix (was Re: [ENH][Unix][VM][2.8][2.9alpha?] stream-based translation)

Rob Withers slosher2 at home.com
Sun Jul 23 11:46:57 UTC 2000


Hi.  There was a problem with the automatic overwriting of a file when
using FileDirectory>>#fileNamed:.  It turns out that when you have an
*existing* file, you will write from the beginning, but it doesn't
eliminate the other contents.  The result is that when you write less
than the previous contents then close it, the file hasn't been
truncated.  This gave me a nice puzzle with the SocketPlugin.c and it
wouldn't compile.  This update adds methods 

FileDirectory>>#overwriteFileNamed: and 
FileStream class>>#overwriteFileNamed:

and fixes up the Builder to use them.

I hope I didn't throw a wrench into someone's work.

cheers,
Rob
-------------- next part --------------
'From Squeak2.8 of 13 June 2000 [latest update: #2348] on 23 July 2000 at 4:36:41 am'!
"Change Set:		translation
Date:			10 July 2000
Author:			Stephan Rudlof

Methods for generating a small VM2.8 squeak binary with one internal and many external plugins (modules).

Should be refactored together with introducing methods just returning Collections of internal/external plugin classes."!

Object subclass: #UnixVMBuilder
	instanceVariableNames: 'rootDir coreVMDir internalModuleDir externalModuleDir exportsDir exports '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'VMConstruction-Interpreter'!

!UnixVMBuilder commentStamp: '<historical>' prior: 0!
This class holds the Module lists and directory structure for the Unix VM source tree.  There are several class side commands which will allow you to regenerate the plugins and interpreter.  It does not generate other platform specific files.

"Full Builds"
doit: [UnixVMBuilder buildThin]
doit: [UnixVMBuilder buildThinnest]
doit: [UnixVMBuilder buildFat]

"Build Selected External Modules"
doit: [UnixVMBuilder buildExternalModule]

"Build the interpreter and internal plugins only"
doit: [UnixVMBuilder buildThinCore]
doit: [UnixVMBuilder buildThinnestCore]
doit: [UnixVMBuilder buildFatCore]

!

!CCodeGenerator methodsFor: 'public' stamp: 'rww 7/22/2000 01:54'!
storeCodeOnStream: aStream doInlining: inlineFlag
	"Store C code for this code base on the given stream."

	self storeCodeOnStream: aStream doInlining: inlineFlag doAssertions: true! !

!CCodeGenerator methodsFor: 'public' stamp: 'rww 7/22/2000 00:55'!
storeCodeOnStream: aStream doInlining: inlineFlag doAssertions: assertionFlag
	"Store C code for this code base on the given stream."

	aStream ifNil: [Error signal: 'Invalid stream during code generation'].
	self emitCCodeOn: aStream doInlining: inlineFlag doAssertions: assertionFlag.
	aStream close.! !


!FileDirectory methodsFor: 'file stream creation' stamp: 'rww 7/23/2000 00:01'!
overwriteFileNamed: localFileName
	"Create a new file with the given name in this directory."

	^ FileStream concreteStream overwriteFileNamed: (self fullNameFor: localFileName)
! !


!FileStream class methodsFor: 'instance creation' stamp: 'rww 7/23/2000 04:36'!
overwriteFileNamed: fileName
 	"Create a new file with the given name, and answer a stream opened for writing on that file. If the file already exists, ask the user what to do."

	| fullName stream |
	fullName _ self fullName: fileName.
	(self isAFileNamed: fullName)
		ifTrue: [
			| dir localName |
			dir _ FileDirectory forFileName: fullName.
			localName _ FileDirectory localNameFor: fullName.
			dir deleteFileNamed: localName
				ifAbsent: [self error: 'Could not delete the old version of that file'].
			stream := self new open: fullName forWrite: true.]
		ifFalse: [stream := self new open: fullName forWrite: true].

	^ stream
! !


!Interpreter class methodsFor: 'translation' stamp: 'rww 7/22/2000 00:46'!
storeExports: exports onStream: aStream
	"Store the exports on the given stream"
	| s |
	s := aStream.
	s nextPutAll:'/* This is an automatically generated table of all named primitive in the VM */'; cr;cr.

	s nextPutAll:'/* Function prototypes */'; cr.
	exports do:[:assoc|
		assoc value do:[:primName|
			s nextPutAll:'int '.
			assoc key size > 0 ifTrue:[
				s nextPutAll: assoc key; nextPutAll:'_'].
			s nextPutAll: primName; nextPutAll:'(void);'; cr.
		].
	].
	s nextPutAll:'/* extra (platform specific) prototypes */'; cr.
	s nextPutAll:'#define XFN(name) int name(void);'; cr.
	s nextPutAll:'#define XFN2(module, name) int module##_##name(void);'; cr.
	s nextPutAll:'#include "platform.exports"'; cr.
	s nextPutAll:'#undef XFN'; cr.
	s nextPutAll:'#undef XFN2'; cr.
	s cr; cr.

	s nextPutAll:'/* Function names */'; cr.
	s nextPutAll:'char *internalPrimitiveNames[][2] = {';cr.
	exports do:[:assoc|
		assoc value do:[:primName|
			s nextPutAll:'{ "'; nextPutAll: assoc key; nextPutAll:'", '.
			s nextPutAll:'"'; nextPutAll: primName; nextPutAll:'" },'; cr.
		].
	].
	s nextPutAll:'/* extra (platform specific) names */'; cr.
	s nextPutAll:'#define XFN(name) { "", #name },'; cr.
	s nextPutAll:'#define XFN2(module, name) { #module, #name },'; cr.
	s nextPutAll:'#include "platform.exports"'; cr.
	s nextPutAll:'#undef XFN'; cr.
	s nextPutAll:'#undef XFN2'; cr.
	s nextPutAll:'{ NULL, NULL }'; cr; nextPutAll:'};'.
	s cr; cr.

	s nextPutAll:'/* Function addresses */'; cr.
	s nextPutAll:'void *internalPrimitiveAddresses[] = {'; cr.
	exports do:[:assoc|
		assoc value do:[:primName|
			s nextPutAll:'(void*)'.
			assoc key size > 0 ifTrue:[
				s nextPutAll: assoc key; nextPutAll:'_'].
			s nextPutAll: primName; nextPutAll:','; cr.
		].
	].
	s nextPutAll:'/* extra (platform specific) addresses */'; cr.
	s nextPutAll:'#define XFN(name) (void*) name,'; cr.
	s nextPutAll:'#define XFN2(module, name) (void*) module##_##name,'; cr.
	s nextPutAll:'#include "platform.exports"'; cr.
	s nextPutAll:'#undef XFN'; cr.
	s nextPutAll:'#undef XFN2'; cr.
	s nextPutAll:'NULL'; cr; nextPutAll:'};'.
	s cr; cr.
	s close.! !

!Interpreter class methodsFor: 'translation new' stamp: 'rww 7/21/2000 23:04'!
translateToInterpreterStream: interpreterStream 
 collectingExports: exportCollection 
 doInlining: inlineFlag 
 forBrowserPlugin: pluginFlag
	"Note: The pluginFlag is meaningless on Windows and Unix. On these 
	platforms Squeak runs as it's own process and doesn't need any special 
	attention from the VMs point of view. Meaning that NONE of the 
	required additional functions will be supported. In other words, the 
	pluginFlag is not needed and not supported."
	"Translate the Smalltalk description of the virtual machine into C. If 
	inlineFlag is true, 
	small method bodies are inlined to reduce procedure call overhead. On 
	the PPC, this results in a factor of three speedup with only 30% 
	increase in code size. If pluginFlag is true, generate code for an 
	interpreter that runs as a browser plugin (Netscape or IE)."
	| doInlining cg |
	doInlining _ inlineFlag.
	pluginFlag ifTrue: [doInlining _ true].
	"must inline when generating browser plugin"
	Interpreter initialize.
	ObjectMemory initialize.
	GenerateBrowserPlugin _ pluginFlag.
	cg _ CCodeGenerator new initialize.
	cg addClass: Interpreter.
	cg addClass: ObjectMemory.
	Interpreter declareCVarsIn: cg.
	ObjectMemory declareCVarsIn: cg.
	"Get all the named prims from the VM. 
	Note: the format of exports is: 
	pluginName -> Array of: primitiveName. 
	so we can generate a nice table from it."
	exportCollection add: ('' -> cg exportedPrimitiveNames asArray).
	cg storeCodeOnStream: interpreterStream doInlining: doInlining.

! !


!InterpreterPlugin class methodsFor: 'translation new' stamp: 'rww 7/21/2000 21:42'!
translateHeaderToStream: aStream
	| fileString |
	fileString := self headerFile.
	fileString isNil
		ifFalse: [ aStream 
			nextPutAll: fileString;
			close].
! !

!InterpreterPlugin class methodsFor: 'translation new' stamp: 'rww 7/22/2000 22:44'!
translateToStream: aStream collectingExports: exports doInlining: inlineFlag locally: localFlag
	"
		|  exports |
		exports := OrderedCollection new.
		self 
			translateToStream: Transcript 
			collectingExports: exports 
			doInlining: true 
			locally: false.
		exports inspect."
	| cg |
	cg := self translateToStream: aStream doInlining: inlineFlag locally: localFlag.
	exports add: (self moduleName -> cg exportedPrimitiveNames asArray).
	^ cg! !

!InterpreterPlugin class methodsFor: 'translation new' stamp: 'rww 7/21/2000 19:36'!
translateToStream: aStream doInlining: inlineFlag locally: localFlag 
	| cg theClass |
	self initialize.
	cg _ self codeGeneratorClass new initialize.
	localFlag ifTrue: [cg pluginPrefix: self moduleName].
	"Add an extra declaration for module name"
	cg declareModuleName: self moduleNameAndVersion local: localFlag.
	theClass _ self.
	[theClass == Object]
		whileFalse: 
			[cg addClass: theClass.
			theClass declareCVarsIn: cg.
			theClass _ theClass superclass].
	cg storeCodeOnStream: aStream doInlining: inlineFlag.
	^ cg! !


!B3DEnginePlugin class methodsFor: 'translation' stamp: 'rww 7/22/2000 00:00'!
translateToStream: aStream doInlining: inlineFlag locally: localFlag 
	| cg |
	self initialize.
	cg _ self codeGeneratorClass new initialize.
	localFlag ifTrue: [cg pluginPrefix: self moduleName].
	"Add an extra declaration for module name"
	cg var: #moduleName declareC: 'const char *moduleName = "', self moduleName,'"'.

	{InterpreterPlugin. B3DEnginePlugin. B3DTransformerPlugin. B3DVertexBufferPlugin. B3DShaderPlugin. B3DClipperPlugin. B3DPickerPlugin. B3DRasterizerPlugin} do: 
		[:theClass | 
		theClass initialize.
		cg addClass: theClass.
		theClass declareCVarsIn: cg].

	cg storeCodeOnStream: aStream doInlining: inlineFlag.
	B3DRasterizerPlugin writeSupportCode: true.

	^ cg
! !


!SurfacePlugin class methodsFor: 'translation' stamp: 'rww 7/22/2000 00:55'!
translateToStream: aStream doInlining: inlineFlag locally: localFlag 
	| cg theClass |
	self initialize.
	cg _ self codeGeneratorClass new initialize.
	localFlag ifTrue: [cg pluginPrefix: self moduleName].
	"Add an extra declaration for module name"
	cg var: #moduleName declareC: 'const char *moduleName = "', self moduleName,'"'.

	theClass _ self.
	[theClass == Object]
		whileFalse: 
			[cg addClass: theClass.
			theClass declareCVarsIn: cg.
			theClass _ theClass superclass].

	"cg storeCodeOnStream: aStream doInlining: inlineFlag."
	aStream nextPutAll: (self sourceCode 
				copyReplaceAll:'$$SURFACE_PLUGIN_STANDALONE$$'
				with: (localFlag ifTrue:['0'] ifFalse:['1'])).
	aStream close.

	^ cg
! !


!UnixVMBuilder methodsFor: 'accessing' stamp: 'rww 7/22/2000 01:38'!
coreVMDir
	| fd |
	fd := self sourceDir.
	self coreVMDirectoryName ifNil: [^fd].
	(fd directoryExists: self coreVMDirectoryName)
		ifFalse: [fd createDirectory: self coreVMDirectoryName].
	^ fd directoryNamed: self coreVMDirectoryName.! !

!UnixVMBuilder methodsFor: 'accessing' stamp: 'rww 7/22/2000 00:31'!
exports
	"Answer the receiver's instance variable exports."

	^exports! !

!UnixVMBuilder methodsFor: 'accessing' stamp: 'rww 7/22/2000 01:38'!
exportsDir
	| fd |
	fd := self sourceDir.
	self exportsDirectoryName ifNil: [^fd].
	(fd directoryExists: self exportsDirectoryName)
		ifFalse: [fd createDirectory: self exportsDirectoryName].
	^ fd directoryNamed: self exportsDirectoryName.! !

!UnixVMBuilder methodsFor: 'accessing' stamp: 'rww 7/22/2000 01:39'!
externalModulesDir
	| fd |
	fd := self sourceDir.
	self externalModulesDirectoryName ifNil: [^fd].
	(fd directoryExists: self externalModulesDirectoryName)
		ifFalse: [fd createDirectory: self externalModulesDirectoryName].
	^ fd directoryNamed: self externalModulesDirectoryName.! !

!UnixVMBuilder methodsFor: 'accessing' stamp: 'rww 7/22/2000 01:40'!
internalModulesDir
	| fd |
	fd := self sourceDir.
	self internalModulesDirectoryName ifNil: [^fd].
	(fd directoryExists: self internalModulesDirectoryName)
		ifFalse: [fd createDirectory: self internalModulesDirectoryName].
	^ fd directoryNamed: self internalModulesDirectoryName.! !

!UnixVMBuilder methodsFor: 'accessing' stamp: 'rww 7/22/2000 00:31'!
rootDir
	"Answer the receiver's instance variable rootDir."

	^rootDir! !

!UnixVMBuilder methodsFor: 'accessing' stamp: 'rww 7/22/2000 01:45'!
sourceDir
	| fd |
	fd := self rootDir.
	fd ifNil: [^ self error: 'bad root directory'].
	self sourceDirectoryName ifNil: [^fd].
	(fd directoryExists: self sourceDirectoryName)
		ifFalse: [fd createDirectory: self sourceDirectoryName].
	^ fd directoryNamed: self sourceDirectoryName.
! !

!UnixVMBuilder methodsFor: 'names' stamp: 'rww 7/22/2000 01:29'!
coreVMDirectoryName
	^'CoreVM'
! !

!UnixVMBuilder methodsFor: 'names' stamp: 'rww 7/22/2000 01:32'!
exportFileName
	^'sqNamedPrims.h'
! !

!UnixVMBuilder methodsFor: 'names' stamp: 'rww 7/22/2000 01:30'!
exportsDirectoryName
	^'CoreVM'
! !

!UnixVMBuilder methodsFor: 'names' stamp: 'rww 7/22/2000 01:41'!
externalModulesDirectoryName
	^'ExternalModules'
! !

!UnixVMBuilder methodsFor: 'names' stamp: 'rww 7/22/2000 01:41'!
internalModulesDirectoryName
	^'InternalModules'
! !

!UnixVMBuilder methodsFor: 'names' stamp: 'rww 7/22/2000 01:31'!
interpreterFileName
	^'interp.c'
! !

!UnixVMBuilder methodsFor: 'names' stamp: 'rww 7/22/2000 01:21'!
rootDirectoryName
	^'Unix_2.8'
! !

!UnixVMBuilder methodsFor: 'names' stamp: 'rww 7/22/2000 01:29'!
sourceDirectoryName
	^'src'
! !

!UnixVMBuilder methodsFor: 'initialize-release' stamp: 'rww 7/22/2000 01:46'!
initialize
	"Wait to initialize the directories"
	exports := OrderedCollection new.
! !

!UnixVMBuilder methodsFor: 'queries' stamp: 'rww 7/22/2000 02:52'!
selectModules
	| questionString selectedModules allModules |
	questionString := 'Selecting Modules', String cr, 'Do you want '.
	allModules := self allModules.
	selectedModules := allModules select: [:eachModule |
		(SelectionMenu confirm: (questionString, eachModule name)) = true].
	^ selectedModules
! !

!UnixVMBuilder methodsFor: 'queries' stamp: 'rww 7/22/2000 02:15'!
shouldBuild
	| warnString |
	warnString := 'This could overwrite existing files.  Are you sure you want to continue?'.
	^ (SelectionMenu confirm: warnString) = true! !

!UnixVMBuilder methodsFor: 'module lists' stamp: 'rww 7/22/2000 02:50'!
allModules
	^ self fatInternalModuleList asOrderedCollection
! !

!UnixVMBuilder methodsFor: 'module lists' stamp: 'rww 7/22/2000 02:39'!
fatExternalModuleList
	^ { }! !

!UnixVMBuilder methodsFor: 'module lists' stamp: 'rww 7/22/2000 02:39'!
fatInternalModuleList
	^ {
			"Graphics"
				"Note: BitBltSimulation should go first, 
				because three of it's entries might be 
				looked up quite often (due to refs from 
				InterpreterProxy). This will go away at
				some point but for now it's a good idea
				to have those entries early in the table."
			BitBltSimulation.	
			BalloonEnginePlugin. 
			SurfacePlugin. "To support OS surfaces through FXBlt"

			"I/O subsystems"
			FilePlugin.
			SocketPlugin. 
			SoundPlugin. 

			SerialPlugin.

	"		MIDIPlugin. 
			JoystickTabletPlugin. 
			AsynchFilePlugin. "		"-> doesn't work with Linux so far"

		 	"Numerics"
			LargeIntegersPlugin.
			FFTPlugin. 
			FloatArrayPlugin. 
			Matrix2x3Plugin. 

			"Compression"
			DeflatePlugin.

			"Note: Optionally, you can translate the following as builtins.
			As of Squeak 2.7 they are not builtins by default:
				DSAPlugin.
				KlattSynthesizerPlugin.
				SoundCodecPlugin.
				B3DEnginePlugin.
				FFIPlugin.
			"
		}! !

!UnixVMBuilder methodsFor: 'module lists' stamp: 'rww 7/22/2000 02:40'!
thinExternalModuleList
	^ {
			"Graphics"
				"Note: BitBltSimulation should go first, 
				because three of it's entries might be 
				looked up quite often (due to refs from 
				InterpreterProxy). This will go away at
				some point but for now it's a good idea
				to have those entries early in the table."
			"BitBltSimulation."	 "->VM"
			BalloonEnginePlugin. 
			SurfacePlugin. "To support OS surfaces through FXBlt"

			"I/O subsystems"
			FilePlugin.
			SocketPlugin. 
			SoundPlugin. 

			SerialPlugin.

	"		MIDIPlugin. 
			JoystickTabletPlugin. 
			AsynchFilePlugin. "		"-> doesn't work with Linux so far"

		 	"Numerics"
			LargeIntegersPlugin.
			FFTPlugin. 
			FloatArrayPlugin. 
			Matrix2x3Plugin. 

			"Compression"
			DeflatePlugin.

			"Note: Optionally, you can translate the following as builtins.
			As of Squeak 2.7 they are not builtins by default:
				DSAPlugin.
				KlattSynthesizerPlugin.
				SoundCodecPlugin.
				B3DEnginePlugin.
				FFIPlugin.
			"
		}! !

!UnixVMBuilder methodsFor: 'module lists' stamp: 'rww 7/22/2000 02:39'!
thinInternalModuleList
	^ { BitBltSimulation }! !

!UnixVMBuilder methodsFor: 'module lists' stamp: 'rww 7/22/2000 02:38'!
thinnestExternalModuleList
	^ {
			"Graphics"
				"Note: BitBltSimulation should go first, 
				because three of it's entries might be 
				looked up quite often (due to refs from 
				InterpreterProxy). This will go away at
				some point but for now it's a good idea
				to have those entries early in the table."
			BitBltSimulation.	
			BalloonEnginePlugin. 
			SurfacePlugin. "To support OS surfaces through FXBlt"

			"I/O subsystems"
			FilePlugin.
			SocketPlugin. 
			SoundPlugin. 

			SerialPlugin.

	"		MIDIPlugin. 
			JoystickTabletPlugin. 
			AsynchFilePlugin. "		"-> doesn't work with Linux so far"

		 	"Numerics"
			LargeIntegersPlugin.
			FFTPlugin. 
			FloatArrayPlugin. 
			Matrix2x3Plugin. 

			"Compression"
			DeflatePlugin.

			"Note: Optionally, you can translate the following as builtins.
			As of Squeak 2.7 they are not builtins by default:
				DSAPlugin.
				KlattSynthesizerPlugin.
				SoundCodecPlugin.
				B3DEnginePlugin.
				FFIPlugin.
			"
		}! !

!UnixVMBuilder methodsFor: 'module lists' stamp: 'rww 7/22/2000 02:39'!
thinnestInternalModuleList
	^ { }! !

!UnixVMBuilder methodsFor: 'api' stamp: 'rww 7/22/2000 02:57'!
buildExternalModule
	| modules |
	self shouldBuild
		ifFalse: [^nil].
	self setupRootDirectory.
	modules := self selectModules.
	self 
		buildExternalModules: modules
! !

!UnixVMBuilder methodsFor: 'api' stamp: 'rww 7/22/2000 02:58'!
buildFat
	self shouldBuild
		ifFalse: [^nil].
	self setupRootDirectory.
	self buildWithInternalModules: self fatInternalModuleList
		externalModules: self fatExternalModuleList
! !

!UnixVMBuilder methodsFor: 'api' stamp: 'rww 7/22/2000 02:58'!
buildFatCore
	self shouldBuild
		ifFalse: [^nil].
	self setupRootDirectory.
	self buildCoreWithInternalModules: self fatInternalModuleList
! !

!UnixVMBuilder methodsFor: 'api' stamp: 'rww 7/22/2000 02:58'!
buildThin
	self shouldBuild
		ifFalse: [^nil].
	self setupRootDirectory.
	self buildWithInternalModules: self thinInternalModuleList
		externalModules: self thinExternalModuleList
! !

!UnixVMBuilder methodsFor: 'api' stamp: 'rww 7/22/2000 02:58'!
buildThinCore
	self shouldBuild
		ifFalse: [^nil].
	self setupRootDirectory.
	self buildCoreWithInternalModules: self thinInternalModuleList
! !

!UnixVMBuilder methodsFor: 'api' stamp: 'rww 7/22/2000 02:58'!
buildThinnest
	self shouldBuild
		ifFalse: [^nil].
	self setupRootDirectory.
	self buildWithInternalModules: self thinnestInternalModuleList
		externalModules: self thinnestExternalModuleList
! !

!UnixVMBuilder methodsFor: 'api' stamp: 'rww 7/22/2000 02:58'!
buildThinnestCore
	self shouldBuild
		ifFalse: [^nil].
	self setupRootDirectory.
	self buildCoreWithInternalModules: self thinnestInternalModuleList
! !

!UnixVMBuilder methodsFor: 'api' stamp: 'rww 7/22/2000 01:46'!
setupRootDirectory
	| response default |
	default := (FileDirectory default 
		directoryNamed: self rootDirectoryName)
		pathName.
	response _ FillInTheBlank request: 'Enter path:'
 		initialAnswer: default.
	(response isEmpty not and: [FileDirectory default fileOrDirectoryExists: response])
		ifTrue: [rootDir := FileDirectory on: response]
		ifFalse: [rootDir := nil.
			self error: 'bad root directory'].

! !

!UnixVMBuilder methodsFor: 'building private' stamp: 'rww 7/22/2000 02:34'!
buildCoreWithInternalModules: internalModules
	self buildInterpreter.
	self buildInternalModules: internalModules.
	self buildExports.

! !

!UnixVMBuilder methodsFor: 'building private' stamp: 'rww 7/23/2000 00:02'!
buildExports
	| exportsFileStream |
	exportsFileStream := self exportsDir overwriteFileNamed: self exportFileName.
	Interpreter storeExports: self exports onStream: exportsFileStream.

! !

!UnixVMBuilder methodsFor: 'building private' stamp: 'rww 7/23/2000 00:02'!
buildExternalModules: externalModules
	externalModules do: [:plugin |
		| cFileStream hFileStream pluginDir |
		pluginDir := self externalModulesDir.
		(pluginDir directoryExists: plugin moduleName)
			ifFalse: [pluginDir createDirectory: plugin moduleName].
		pluginDir := pluginDir directoryNamed: plugin moduleName.
		hFileStream := pluginDir 
			overwriteFileNamed: (plugin moduleName, '.h').
		cFileStream := pluginDir 
			overwriteFileNamed: (plugin moduleName, plugin moduleExtension).
		plugin translateHeaderToStream: hFileStream.
		plugin 
			translateToStream: cFileStream 
			doInlining: true 
			locally: false.
	].
! !

!UnixVMBuilder methodsFor: 'building private' stamp: 'rww 7/23/2000 00:02'!
buildInternalModules: internalModules
	internalModules do: [:plugin |
		| cFileStream pluginDir |
		pluginDir := self internalModulesDir.
		cFileStream := pluginDir 
			overwriteFileNamed: (plugin moduleName, plugin moduleExtension).
		plugin 
			translateToStream: cFileStream 
			collectingExports: self exports 
			doInlining: true 
			locally: true.
	].

! !

!UnixVMBuilder methodsFor: 'building private' stamp: 'rww 7/23/2000 00:02'!
buildInterpreter
	| interpreterFileStream |
	interpreterFileStream := self coreVMDir overwriteFileNamed: self interpreterFileName.
	Interpreter 
		translateToInterpreterStream: interpreterFileStream 
		collectingExports: self exports 
		doInlining: true 
		forBrowserPlugin: false.

! !

!UnixVMBuilder methodsFor: 'building private' stamp: 'rww 7/22/2000 02:35'!
buildWithInternalModules: internalModules externalModules: externalModules
	self buildCoreWithInternalModules: internalModules.
	self buildExternalModules: externalModules.

! !


!UnixVMBuilder class methodsFor: 'instance creation' stamp: 'rww 7/22/2000 00:59'!
new
	^super new initialize! !

!UnixVMBuilder class methodsFor: 'build generation' stamp: 'rww 7/22/2000 02:29'!
buildExternalModule
	"self buildExternalModule"
	self new buildExternalModule.
! !

!UnixVMBuilder class methodsFor: 'build generation' stamp: 'rww 7/22/2000 02:55'!
buildFat
	"self buildFat"
	self new buildFat.
! !

!UnixVMBuilder class methodsFor: 'build generation' stamp: 'rww 7/22/2000 02:56'!
buildFatCore
	"self buildFatCore"
	self new buildFatCore.
! !

!UnixVMBuilder class methodsFor: 'build generation' stamp: 'rww 7/22/2000 02:55'!
buildThin
	"self buildThin"
	self new buildThin.
! !

!UnixVMBuilder class methodsFor: 'build generation' stamp: 'rww 7/22/2000 02:57'!
buildThinCore
	"self buildThinCore"
	self new buildThinCore.
! !

!UnixVMBuilder class methodsFor: 'build generation' stamp: 'rww 7/22/2000 02:55'!
buildThinnest
	"self buildThinnest"
	self new buildThinnest.
! !

!UnixVMBuilder class methodsFor: 'build generation' stamp: 'rww 7/22/2000 02:57'!
buildThinnestCore
	"self buildThinnestCore"
	self new buildThinnestCore.
! !


!UnixVMBuilder reorganize!
('accessing' coreVMDir exports exportsDir externalModulesDir internalModulesDir rootDir sourceDir)
('names' coreVMDirectoryName exportFileName exportsDirectoryName externalModulesDirectoryName internalModulesDirectoryName interpreterFileName rootDirectoryName sourceDirectoryName)
('initialize-release' initialize)
('queries' selectModules shouldBuild)
('module lists' allModules fatExternalModuleList fatInternalModuleList thinExternalModuleList thinInternalModuleList thinnestExternalModuleList thinnestInternalModuleList)
('api' buildExternalModule buildFat buildFatCore buildThin buildThinCore buildThinnest buildThinnestCore setupRootDirectory)
('building private' buildCoreWithInternalModules: buildExports buildExternalModules: buildInternalModules: buildInterpreter buildWithInternalModules:externalModules:)
!



More information about the Squeak-dev mailing list