[Vm-dev] VM Maker: VMMaker-oscog-GuillermoPolito.240.mcz

commits at source.squeak.org commits at source.squeak.org
Tue Jun 18 08:16:11 UTC 2013


Guillermo Polito uploaded a new version of VMMaker to project VM Maker:
http://source.squeak.org/VMMaker/VMMaker-oscog-GuillermoPolito.240.mcz

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

Name: VMMaker-oscog-GuillermoPolito.240
Author: GuillermoPolito
Time: 17 June 2013, 4:16:37.382 pm
UUID: 262dff38-4bb7-450f-afaf-a4ba4c648554
Ancestors: VMMaker-oscog-EstebanLorenzano.239

changing references from FileDirectory to FileSystem

=============== Diff against VMMaker-oscog-EstebanLorenzano.239 ===============

Item was removed:
- SystemOrganization addCategory: #'VMMaker-Building'!
- SystemOrganization addCategory: #'VMMaker-JIT'!
- SystemOrganization addCategory: #'VMMaker-Interpreter'!
- SystemOrganization addCategory: #'VMMaker-InterpreterSimulation'!
- SystemOrganization addCategory: #'VMMaker-JITSimulation'!
- SystemOrganization addCategory: #'VMMaker-Translation to C'!
- SystemOrganization addCategory: #'VMMaker-Support'!
- SystemOrganization addCategory: #'VMMaker-PostProcessing'!
- SystemOrganization addCategory: #'VMMaker-MemoryManager'!
- SystemOrganization addCategory: #'VMMaker-MemoryManagerSimulation'!
- SystemOrganization addCategory: #'VMMaker-Multithreading'!
- SystemOrganization addCategory: #'VMMaker-Tests'!
- SystemOrganization addCategory: #'VMMaker-Plugins'!
- SystemOrganization addCategory: #'VMMaker-SmartSyntaxPlugins'!
- SystemOrganization addCategory: #'VMMaker-Plugins-Alien'!
- SystemOrganization addCategory: #'VMMaker-Plugins-IOS'!

Item was added:
+ SystemOrganization addCategory: #VMMaker!
+ SystemOrganization addCategory: #'VMMaker-Building'!
+ SystemOrganization addCategory: #'VMMaker-Interpreter'!
+ SystemOrganization addCategory: #'VMMaker-InterpreterSimulation'!
+ SystemOrganization addCategory: #'VMMaker-JIT'!
+ SystemOrganization addCategory: #'VMMaker-JITSimulation'!
+ SystemOrganization addCategory: #'VMMaker-MemoryManager'!
+ SystemOrganization addCategory: #'VMMaker-MemoryManagerSimulation'!
+ SystemOrganization addCategory: #'VMMaker-Multithreading'!
+ SystemOrganization addCategory: #'VMMaker-Plugins'!
+ SystemOrganization addCategory: #'VMMaker-Plugins-Alien'!
+ SystemOrganization addCategory: #'VMMaker-Plugins-IOS'!
+ SystemOrganization addCategory: #'VMMaker-PostProcessing'!
+ SystemOrganization addCategory: #'VMMaker-SmartSyntaxPlugins'!
+ SystemOrganization addCategory: #'VMMaker-Support'!
+ SystemOrganization addCategory: #'VMMaker-Tests'!
+ SystemOrganization addCategory: #'VMMaker-Translation to C'!

Item was changed:
  ----- Method: CCodeGenerator>>extractTypeFor:fromDeclaration: (in category 'utilities') -----
  extractTypeFor: aVariable fromDeclaration: aVariableDeclaration
  	"Eliminate inessentials from aVariableDeclaration to answer a C type without the variable,
  	 or initializations etc"
  	| decl fpIndex |
  	decl := aVariableDeclaration.
  	(decl beginsWith: 'static') ifTrue:
  		[decl := decl allButFirst: 6].
  	(decl indexOf: $= ifAbsent: []) ifNotNil:
  		[:index| decl := decl copyFrom: 1 to: index - 1].
  	decl := decl copyReplaceAll: aVariable with: '' tokenish: [:ch| ch = $_ or: [ch isAlphaNumeric]].
  	(fpIndex := decl indexOfSubCollection: '(*') > 0 ifTrue:
  		[decl := decl copyReplaceFrom: (decl indexOf: $( startingAt: fpIndex + 1)
  					to: (decl indexOf: $) startingAt: fpIndex + 1)
  					with: ''].
+ 	^decl trimBoth!
- 	^decl withBlanksTrimmed!

Item was changed:
  ----- Method: CCodeGenerator>>needToGenerateHeader:file:contents: (in category 'C code generator') -----
  needToGenerateHeader: headerName file: interpHdrPath contents: newContentsArg
  	"Check if we need to regenerate a header file.  We always need to if the contents have changed.
  	 But if not we can avoid needless recompilations by not regenerating.  So only regenerate if the
  	 package is clean (version doesn't include a '*').  If we can't find a package version ask the user."
+ 
  	| newContents oldContents |
+ 	interpHdrPath asFileReference exists
+ 		ifFalse: [ ^ true ].
- 	(FileDirectory default fileExists: interpHdrPath) ifFalse:
- 		[^true].
  	newContents := newContentsArg.
+ 	oldContents := (FileStream oldFileNamed: interpHdrPath) contentsOfEntireFile.
+ 	(newContents beginsWith: '/*') = (oldContents beginsWith: '/*')
+ 		ifFalse: [ 
+ 			(newContents beginsWith: '/*')
+ 				ifTrue: [ 
+ 					newContents := newContents readStream
+ 						upToAll: '*/';
+ 						skipSeparators;
+ 						upToEnd ].
+ 			(oldContents beginsWith: '/*')
+ 				ifTrue: [ 
+ 					oldContents := oldContents readStream
+ 						upToAll: '*/';
+ 						skipSeparators;
+ 						upToEnd ] ].
+ 	oldContents := oldContents
+ 		copyReplaceAll:
+ 			{(Character cr).
+ 			(Character lf)}
+ 		with: {(Character cr)}.
- 	oldContents := (FileDirectory default oldFileNamed: interpHdrPath) contentsOfEntireFile.
- 	(newContents beginsWith: '/*') = (oldContents beginsWith: '/*') ifFalse:
- 		[(newContents beginsWith: '/*') ifTrue:
- 			[newContents := newContents readStream upToAll: '*/'; skipSeparators; upToEnd].
- 		 (oldContents beginsWith: '/*') ifTrue:
- 			[oldContents := oldContents readStream upToAll: '*/'; skipSeparators; upToEnd]].
- 	oldContents := oldContents copyReplaceAll: {Character cr. Character lf} with: {Character cr}.
  	oldContents replaceAll: Character lf with: Character cr.
+ 	^ oldContents ~= newContents
+ 		or: [ 
+ 			[ ((self class monticelloDescriptionFor: vmClass) includes: $*) not ]
+ 				on: Error
+ 				do: [ :ex | 
+ 					self
+ 						confirm:
+ 							headerName
+ 								,
+ 									' contents are unchanged.\Writing the file may cause recompilation of support files.\Do you want to write the header file?\The interpreter will still be written either way.'
+ 										withCRs ] ]!
- 	^oldContents ~= newContents
- 	 or: [[((self class monticelloDescriptionFor: vmClass) includes: $*) not]
- 			on: Error
- 			do: [:ex|
- 				self confirm: headerName, ' contents are unchanged.\Writing the file may cause recompilation of support files.\Do you want to write the header file?\The interpreter will still be written either way.' withCRs]]!

Item was changed:
  ----- Method: CCodeGenerator>>structClassesForTranslationClasses: (in category 'utilities') -----
  structClassesForTranslationClasses: classes
  	"Answer in superclass order (any superclass precedes any subclass) the ancilliaryStructClasses for all the given classes."
  	| structClasses |
  
  	structClasses := Set new.
  	classes do:
  		[:aTranslationClass|
  		structClasses addAll:
  			([aTranslationClass ancilliaryStructClasses]
  				on: MessageNotUnderstood
  				do: [:ex|
  					ex message selector == #ancilliaryStructClasses
  						ifTrue: [#()]
  						ifFalse: [ex pass]])].
+ 	^Class superclassOrder: structClasses asArray!
- 	^ChangeSet superclassOrder: structClasses asArray!

Item was changed:
  ----- Method: CogVMSimulator>>openAsMorph (in category 'UI') -----
  openAsMorph
  	"Open a morphic view on this simulation."
  	| localImageName borderWidth theWindow |
+ 	localImageName := FileSystem workingDirectory localNameFor: imageName.
- 	localImageName := FileDirectory default localNameFor: imageName.
  	theWindow := (SystemWindow labelled: 'Simulation of ', localImageName) model: self.
  
  	theWindow addMorph: (displayView := ImageMorph new image: displayForm)
  		frame: (0 at 0 corner: 1 at 0.8).
  
  	transcript := TranscriptStream on: (String new: 10000).
  	theWindow addMorph: (PluggableTextMorph
  							on: transcript text: nil accept: nil
  							readSelection: nil menu: #codePaneMenu:shifted:)
  			frame: (0 at 0.8 corner: 0.7 at 1).
  	theWindow addMorph: (PluggableTextMorph on: self
  						text: #byteCountText accept: nil
  						readSelection: nil menu: #utilitiesMenu:) hideScrollBarsIndefinitely
  			frame: (0.7 at 0.8 corner: 1 at 1).
  
  	borderWidth := [SystemWindow borderWidth] "Squeak 4.1"
  						on: MessageNotUnderstood
  						do: [:ex| 0]. "3.8"
  	borderWidth := borderWidth + theWindow borderWidth.
  	theWindow openInWorldExtent: (self desiredDisplayExtent
  								+ (2 * borderWidth)
  								+ (0 at theWindow labelHeight)
  								* (1@(1/0.8))) rounded!

Item was changed:
  ----- Method: CogVMSimulator>>openAsMorphNoTranscript (in category 'UI') -----
  openAsMorphNoTranscript
  	"Open a morphic view on this simulation."
  	| localImageName theWindow |
+ 	localImageName := FileSystem workingDirectory localNameFor: imageName.
- 	localImageName := FileDirectory default localNameFor: imageName.
  	theWindow := (SystemWindow labelled: 'Simulation of ' , localImageName) model: self.
  
  	theWindow addMorph: (displayView := ImageMorph new image: displayForm)
  		frame: (0 at 0 corner: 1 at 0.95).
  
  	theWindow addMorph: (PluggableTextMorph on: self
  						text: #byteCountText accept: nil
  						readSelection: nil menu: #utilitiesMenu:) hideScrollBarsIndefinitely
  		frame: (0 at 0.95 corner: 1 at 1).
  
  	theWindow openInWorldExtent: (self desiredDisplayExtent
  								+ (2 * theWindow borderWidth)
  								+ (0 at theWindow labelHeight)
  								* (1@(1/0.95))) rounded!

Item was changed:
  ----- Method: CogVMSimulator>>primitiveDirectoryEntry (in category 'file primitives') -----
  primitiveDirectoryEntry
  	| name pathName array result |
  	name := self stringOf: self stackTop.
  	pathName := self stringOf: (self stackValue: 1).
  	
  	self successful ifFalse:
  		[^self primitiveFail].
  
+ 	array := FileSystem workingDirectory primLookupEntryIn: pathName name: name.
- 	array := FileDirectory default primLookupEntryIn: pathName name: name.
  	array == nil ifTrue:
  		[self pop: 3 thenPush: objectMemory nilObject.
  		^array].
  	array == #badDirectoryPath ifTrue:
  		[self halt.
  		^self primitiveFail].
  
  	result := self makeDirEntryName: (array at: 1) 
  		size: (array at: 1) size
  		createDate: (array at: 2) 
  		modDate: (array at: 3)
  		isDir: (array at: 4)  
  		fileSize: (array at: 5)
  		posixPermissions: (array at: 6)
  		isSymlink: (array at: 7).
  	
  	self pop: 3.
  	self push: result!

Item was changed:
  ----- Method: CogVMSimulator>>primitiveDirectoryLookup (in category 'file primitives') -----
  primitiveDirectoryLookup
  	| index pathName array result |
  	index := self stackIntegerValue: 0.
  	pathName := (self stringOf: (self stackValue: 1)).
  	
  	self successful ifFalse:
  		[^self primitiveFail].
  
+ 	array := FileSystem workingDirectory primLookupEntryIn: pathName index: index.
- 	array := FileDirectory default primLookupEntryIn: pathName index: index.
  
  	array == nil ifTrue:
  		[self pop: 3 thenPush: objectMemory nilObject.
  		^array].
  	array == #badDirectoryPath ifTrue:
  		["self halt."
  		^self primitiveFail].
  
  	result := self makeDirEntryName: (array at: 1) 
  		size: (array at: 1) size
  		createDate: (array at: 2) 
  		modDate: (array at: 3)
  		isDir: (array at: 4)  
  		fileSize: (array at: 5)
  		posixPermissions: (array at: 6)
  		isSymlink: (array at: 7).
  	self pop: 3 thenPush: result!

Item was changed:
  ----- Method: FilePlugin>>asciiDirectoryDelimiter (in category 'directory primitives') -----
  asciiDirectoryDelimiter
+ 	^ self cCode: 'dir_Delimitor()' inSmalltalk: [FileSystem disk delimiter asciiValue]!
- 	^ self cCode: 'dir_Delimitor()' inSmalltalk: [FileDirectory pathNameDelimiter asciiValue]!

Item was changed:
  ----- Method: FilePluginSimulator>>sqFileDeleteName:Size: (in category 'simulation') -----
  sqFileDeleteName: nameIndex Size: nameSize
  	| path |
  	path := interpreterProxy interpreter asString: nameIndex size: nameSize.
  	(StandardFileStream isAFileNamed: path) ifFalse:
  		[^interpreterProxy primitiveFail].
+ 	[path asFileReference ensureDeleted]
- 	[FileDirectory deleteFilePath: path]
  		on: Error
  		do: [:ex| interpreterProxy primitiveFail]!

Item was changed:
  ----- Method: FilePluginSimulator>>sqFileRenameOld:Size:New:Size: (in category 'simulation') -----
  sqFileRenameOld: oldNameIndex Size: oldNameSize New: newNameIndex Size: newNameSize
  	| oldPath newPath |
+ 	oldPath := FileSystem workingDirectory fullNameFor: (interpreterProxy interpreter asString: oldNameIndex size: oldNameSize).
+ 	newPath := FileSystem workingDirectory fullNameFor: (interpreterProxy interpreter asString: newNameIndex size: newNameSize).
- 	oldPath := FileDirectory default fullNameFor: (interpreterProxy interpreter asString: oldNameIndex size: oldNameSize).
- 	newPath := FileDirectory default fullNameFor: (interpreterProxy interpreter asString: newNameIndex size: newNameSize).
  	((StandardFileStream isAFileNamed: oldPath)
  	 and: [(StandardFileStream isAFileNamed: newPath) not]) ifFalse:
  		[^interpreterProxy primitiveFail].
+ 	[FileSystem workingDirectory primRename: oldPath to: newPath]
- 	[FileDirectory default primRename: oldPath to: newPath]
  		on: Error
  		do: [:ex| interpreterProxy primitiveFail]!

Item was changed:
  ----- Method: Gnuifier class>>on: (in category 'as yet unclassified') -----
  on: aFilePathStringOrDirectory
+ 	^ self new
+ 		setDirectory:
+ 			(aFilePathStringOrDirectory isString
+ 				ifTrue: [ aFilePathStringOrDirectory asFileReference ]
+ 				ifFalse: [ aFilePathStringOrDirectory ])!
- 
- 	^self new setDirectory: (aFilePathStringOrDirectory isString
- 								ifTrue: [FileDirectory on: aFilePathStringOrDirectory]
- 								ifFalse: [aFilePathStringOrDirectory])!

Item was changed:
  ----- Method: Interpreter class>>macroBenchmark (in category 'benchmarks') -----
  macroBenchmark  "Interpreter macroBenchmark"
  	"Copied from Interpreter class>>translate:doInlining:forBrowserPlugin:"
  	| cg fileName |
  	fileName := 'benchmark2.out'.
  	Interpreter initialize.
  	ObjectMemory initialize.
  	cg := CCodeGenerator new initialize.
  	Interpreter initialize.
  	ObjectMemory initializeWithOptions: (Dictionary new
  											at: #BytesPerWord put: 4;
  											yourself).
  	cg addClass: Interpreter.
  	cg addClass: ObjectMemory.
  	Interpreter declareCVarsIn: cg.
  	ObjectMemory declareCVarsIn: cg.
+ 	FileSystem workingDirectory deleteFileNamed: fileName.
- 	FileDirectory default deleteFileNamed: fileName.
  	cg storeCodeOnFile: fileName doInlining: true.
+ 	FileSystem workingDirectory deleteFileNamed: fileName.!
- 	FileDirectory default deleteFileNamed: fileName.!

Item was changed:
  ----- Method: InterpreterPlugin class>>baseDirectoryName (in category 'translation') -----
  baseDirectoryName
  	"Return the directory into which plugins should be generated by default."
+ 	^FileSystem workingDirectory pathName!
- 	^FileDirectory default pathName!

Item was changed:
  ----- Method: InterpreterPlugin class>>translateInDirectory:doInlining: (in category 'translation') -----
  translateInDirectory: directory doInlining: inlineFlag
  "This is the default method for writing out sources for a plugin. Several classes need special handling, so look at all implementors of this message"
  	| cg fname fstat |
  	 fname := self moduleName, '.c'.
  
  	"don't translate if the file is newer than my timeStamp"
  	fstat := directory entryAt: fname ifAbsent:[nil].
  	fstat ifNotNil:
  		[((self pluginClassesUpTo: self) allSatisfy:
+ 				[ :aPluginClass| aPluginClass timeStamp < fstat modificationTime asSeconds ]) ifTrue:
- 				[:aPluginClass| aPluginClass timeStamp < fstat modificationTime]) ifTrue:
  			[^nil]].
  
  	self initialize.
  	cg := self buildCodeGeneratorUpTo: self.
  	cg storeCodeOnFile:  (directory fullNameFor: fname) doInlining: inlineFlag.
  	^cg exportedPrimitiveNames asArray!

Item was changed:
  ----- Method: InterpreterSimulator>>openAsMorph (in category 'UI') -----
  openAsMorph
  	"Open a morphic view on this simulation."
  	| window localImageName |
+ 	localImageName := FileSystem workingDirectory localNameFor: imageName.
- 	localImageName := FileDirectory default localNameFor: imageName.
  	window := (SystemWindow labelled: 'Simulation of ' , localImageName) model: self.
  
  	window addMorph: (displayView := ImageMorph new image: displayForm)
  		frame: (0 at 0 corner: 1 at 0.8).
  
  	transcript := TranscriptStream on: (String new: 10000).
  	window addMorph: (PluggableTextMorph on: transcript text: nil accept: nil
  			readSelection: nil menu: #codePaneMenu:shifted:)
  		frame: (0 at 0.8 corner: 0.7 at 1).
  
  	window addMorph: (PluggableTextMorph on: self
  						text: #byteCountText accept: nil) hideScrollBarsIndefinitely
  		frame: (0.7 at 0.8 corner: 1 at 1).
  
  	window openInWorld!

Item was changed:
  ----- Method: InterpreterSimulator>>primitiveDirectoryEntry (in category 'file primitives') -----
  primitiveDirectoryEntry
  	| name pathName array result |
  	name := self stringOf: self stackTop.
  	pathName := self stringOf: (self stackValue: 1).
  	
  	successFlag ifFalse:
  		[^self primitiveFail].
  
+ 	array := FileSystem workingDirectory primLookupEntryIn: pathName name: name.
- 	array := FileDirectory default primLookupEntryIn: pathName name: name.
  	array == nil ifTrue:
  		[self pop: 3 thenPush: nilObj.
  		^array].
  	array == #badDirectoryPath ifTrue:
  		[self halt.
  		^self primitiveFail].
  
  	result := self makeDirEntryName: (array at: 1) 
  		size: (array at: 1) size
  		createDate: (array at: 2) 
  		modDate: (array at: 3)
  		isDir: (array at: 4)  
  		fileSize: (array at: 5)
  		posixPermissions: (array at: 6)
  		isSymlink: (array at: 7).
  	self pop: 3.
  	self push: result!

Item was changed:
  ----- Method: InterpreterSimulator>>primitiveDirectoryLookup (in category 'file primitives') -----
  primitiveDirectoryLookup
  	| index pathName array result |
  	index := self stackIntegerValue: 0.
  	pathName := (self stringOf: (self stackValue: 1)).
  	
  	successFlag ifFalse: [
  		^self primitiveFail.
  	].
  
+ 	array := FileSystem workingDirectory primLookupEntryIn: pathName index: index.
- 	array := FileDirectory default primLookupEntryIn: pathName index: index.
  
  	array == nil ifTrue: [
  		self pop: 3.
  		self push: nilObj.
  		^array.
  	].
  	array == #badDirectoryPath ifTrue: [self halt.
  		^self primitiveFail.
  	].
  
  	result := self makeDirEntryName: (array at: 1) 
  		size: (array at: 1) size
  		createDate: (array at: 2) 
  		modDate: (array at: 3)
  		isDir: (array at: 4)  
  		fileSize: (array at: 5)
  		posixPermissions: (array at: 6)
  		isSymlink: (array at: 7).
  	self pop: 3.
  	self push: result.
  !

Item was changed:
  ----- Method: MiscPrimitivePlugin class>>translateInDirectory:doInlining: (in category 'translation') -----
  translateInDirectory: directory doInlining: inlineFlag
  "handle a special case code string rather than normal generated code."
  	| cg fname fstat |
  	 fname := self moduleName, '.c'.
  
  	"don't translate if the file is newer than my timeStamp"
  	fstat := directory entryAt: fname ifAbsent:[nil].
+ 	fstat ifNotNil:[self timeStamp < fstat modificationTime asSeconds ifTrue:[^nil]].
- 	fstat ifNotNil:[self timeStamp < fstat modificationTime ifTrue:[^nil]].
  
  	self initialize.
  	cg := self buildCodeGeneratorUpTo: InterpreterPlugin.
  	cg addMethodsForPrimitives: self translatedPrimitives.
  	self storeString: cg generateCodeStringForPrimitives onFileNamed: (directory fullNameFor: fname).
  	^cg exportedPrimitiveNames asArray
  !

Item was changed:
  ----- Method: NewspeakInterpreterSimulator>>openAsMorph (in category 'UI') -----
  openAsMorph
  	"Open a morphic view on this simulation."
  	| window localImageName |
+ 	localImageName := FileSystem workingDirectory localNameFor: imageName.
- 	localImageName := FileDirectory default localNameFor: imageName.
  	window := (SystemWindow labelled: 'Simulation of ', localImageName) model: self.
  
  	window addMorph: (displayView := ImageMorph new image: displayForm)
  		frame: (0 at 0 corner: 1 at 0.8).
  
  	transcript := TranscriptStream on: (String new: 10000).
  	window addMorph: (PluggableTextMorph
  							on: transcript text: nil accept: nil
  							readSelection: nil menu: #codePaneMenu:shifted:)
  			frame: (0 at 0.8 corner: 0.7 at 1).
  
  	window addMorph: (PluggableTextMorph on: self
  						text: #byteCountText accept: nil
  						readSelection: nil menu: #utilitiesMenu:) hideScrollBarsIndefinitely
  			frame: (0.7 at 0.8 corner: 1 at 1).
  
  	window openInWorldExtent: (self desiredDisplayExtent
  								+ (2 * window borderWidth)
  								+ (0 at window labelHeight)
  								* (1@(1/0.8))) rounded!

Item was changed:
  ----- Method: NewspeakInterpreterSimulator>>openAsMorphNoTranscript (in category 'UI') -----
  openAsMorphNoTranscript
  	"Open a morphic view on this simulation."
  	| window localImageName |
+ 	localImageName := FileSystem workingDirectory localNameFor: imageName.
- 	localImageName := FileDirectory default localNameFor: imageName.
  	window := (SystemWindow labelled: 'Simulation of ' , localImageName) model: self.
  
  	window addMorph: (displayView := ImageMorph new image: displayForm)
  		frame: (0 at 0 corner: 1 at 0.95).
  
  	window addMorph: (PluggableTextMorph on: self
  						text: #byteCountText accept: nil) hideScrollBarsIndefinitely
  		frame: (0 at 0.95 corner: 1 at 1).
  
  	window openInWorldExtent: (self desiredDisplayExtent
  								+ (2 * window borderWidth)
  								+ (0 at window labelHeight)
  								* (1@(1/0.95))) rounded!

Item was changed:
  ----- Method: NewspeakInterpreterSimulator>>primitiveDirectoryEntry (in category 'file primitives') -----
  primitiveDirectoryEntry
  	| name pathName array result |
  	name := self stringOf: self stackTop.
  	pathName := self stringOf: (self stackValue: 1).
  	
  	self successful ifFalse:
  		[^self primitiveFail].
  
+ 	array := FileSystem workingDirectory primLookupEntryIn: pathName name: name.
- 	array := FileDirectory default primLookupEntryIn: pathName name: name.
  	array == nil ifTrue:
  		[self pop: 3 thenPush: nilObj.
  		^array].
  	array == #badDirectoryPath ifTrue:
  		[self halt.
  		^self primitiveFail].
  
  	result := self makeDirEntryName: (array at: 1) 
  		size: (array at: 1) size
  		createDate: (array at: 2) 
  		modDate: (array at: 3)
  		isDir: (array at: 4)  
  		fileSize: (array at: 5)
  		posixPermissions: (array at: 6)
  		isSymlink: (array at: 7).
  	self pop: 3.
  	self push: result!

Item was changed:
  ----- Method: NewspeakInterpreterSimulator>>primitiveDirectoryLookup (in category 'file primitives') -----
  primitiveDirectoryLookup
  	| index pathName array result |
  	index := self stackIntegerValue: 0.
  	pathName := (self stringOf: (self stackValue: 1)).
  	
  	self successful ifFalse: [
  		^self primitiveFail.
  	].
  
+ 	array := FileSystem workingDirectory primLookupEntryIn: pathName index: index.
- 	array := FileDirectory default primLookupEntryIn: pathName index: index.
  
  	array == nil ifTrue: [
  		self pop: 3.
  		self push: nilObj.
  		^array.
  	].
  	array == #badDirectoryPath ifTrue: [self halt.
  		^self primitiveFail.
  	].
  
  	result := self makeDirEntryName: (array at: 1) 
  		size: (array at: 1) size
  		createDate: (array at: 2) 
  		modDate: (array at: 3)
  		isDir: (array at: 4)  
  		fileSize: (array at: 5)
  		posixPermissions: (array at: 6)
  		isSymlink: (array at: 7).
  	self pop: 3.
  	self push: result.
  !

Item was changed:
  ----- Method: RiscOSVMMaker class>>generateSqueakStackVM (in category 'configurations') -----
  generateSqueakStackVM
  	"RISC OS version; build needed plugins, make sure filename tweaking is used"
  "RiscOSVMMaker generateSqueakStackVM"
  	^self
  		generate: StackInterpreter
+ 		to: (FileSystem workingDirectory directoryNamed: 'stacksrc') fullName
+ 		platformDir: (FileSystem workingDirectory directoryNamed: 'platforms') fullName
- 		to: (FileDirectory default directoryNamed: 'stacksrc') fullName
- 		platformDir: (FileDirectory default directoryNamed: 'platforms') fullName
  		excluding: #(AsynchFilePlugin BrokenPlugin CroquetPlugin FFIPlugin IA32ABIPlugin ImmX11Plugin InternetConfigPlugin JoystickTabletPlugin MIDIPlugin MacMenubarPlugin Mpeg3Plugin NewsqueakIA32ABIPlugin QuicktimePlugin SerialPlugin  TestOSAPlugin ThreadedARMFFIPlugin ThreadedFFIPlugin ThreadedIA32FFIPlugin ThreadedPPCBEFFIPlugin UUIDPlugin VMProfileMacSupportPlugin)!

Item was changed:
  ----- Method: StackInterpreter class>>macroBenchmark (in category 'benchmarks') -----
+ macroBenchmark
+ 	"StackInterpreter macroBenchmark"
+ 
- macroBenchmark  "StackInterpreter macroBenchmark"
  	| dir |
+ 	dir := 'benchmark2.dir' asFileReference.
+ 	dir isDirectory
+ 		ifTrue: [ dir deleteAllChildren ]
+ 		ifFalse: [ dir ensureDirectory ].
+ 	([ 
+ 	VMMaker
+ 		makerFor: StackInterpreter
+ 		and: nil
+ 		with: #()
+ 		to: dir asFileReference fullName
+ 		platformDir: 'none'
+ 		excluding: (InterpreterPlugin withAllSubclasses collect: [ :ea | ea name ]) ]
+ 		on: VMMakerException
+ 		do: [ :ex | ex resume: nil ]) generateInterpreterFile.	"suppress bleats about non-existent platforms dir"
+ 	dir
+ 		deleteAllChildren;
+ 		recursiveDelete!
- 	dir := 'benchmark2.dir'.
- 	(FileDirectory default directoryExists: dir)
- 		ifTrue: [(FileDirectory default directoryNamed: dir) recursiveDeleteContents]
- 		ifFalse: [(FileDirectory default directoryNamed: dir) assureExistence].
- 	([VMMaker
- 			makerFor: StackInterpreter
- 			and: nil
- 			with: #()
- 			to: (FileDirectory default pathFromURI: dir)
- 			platformDir: 'none'
- 			excluding:  (InterpreterPlugin withAllSubclasses collect: [:ea| ea name])]
- 		on: VMMakerException "suppress bleats about non-existent platforms dir"
- 		do: [:ex| ex resume: nil])
- 			generateInterpreterFile.
- 	(FileDirectory default directoryNamed: dir) recursiveDeleteContents; recursiveDelete!

Item was changed:
  ----- Method: StackInterpreterSimulator>>openAsMorph (in category 'UI') -----
  openAsMorph
  	"Open a morphic view on this simulation."
  	| window localImageName |
+ 	localImageName := FileSystem workingDirectory localNameFor: imageName.
- 	localImageName := FileDirectory default localNameFor: imageName.
  	window := (SystemWindow labelled: 'Simulation of ', localImageName) model: self.
  
  	window addMorph: (displayView := ImageMorph new image: displayForm)
  		frame: (0 at 0 corner: 1 at 0.8).
  
  	transcript := TranscriptStream on: (String new: 10000).
  	window addMorph: (PluggableTextMorph
  							on: transcript text: nil accept: nil
  							readSelection: nil menu: #codePaneMenu:shifted:)
  			frame: (0 at 0.8 corner: 0.7 at 1).
  
  	window addMorph: (PluggableTextMorph on: self
  						text: #byteCountText accept: nil
  						readSelection: nil menu: #utilitiesMenu:) hideScrollBarsIndefinitely
  			frame: (0.7 at 0.8 corner: 1 at 1).
  
  	window openInWorldExtent: (self desiredDisplayExtent
  								+ (2 * window borderWidth)
  								+ (0 at window labelHeight)
  								* (1@(1/0.8))) rounded!

Item was changed:
  ----- Method: StackInterpreterSimulator>>openAsMorphNoTranscript (in category 'UI') -----
  openAsMorphNoTranscript
  	"Open a morphic view on this simulation."
  	| window localImageName |
+ 	localImageName := FileSystem workingDirectory localNameFor: imageName.
- 	localImageName := FileDirectory default localNameFor: imageName.
  	window := (SystemWindow labelled: 'Simulation of ' , localImageName) model: self.
  
  	window addMorph: (displayView := ImageMorph new image: displayForm)
  		frame: (0 at 0 corner: 1 at 0.95).
  
  	window addMorph: (PluggableTextMorph on: self
  						text: #byteCountText accept: nil) hideScrollBarsIndefinitely
  		frame: (0 at 0.95 corner: 1 at 1).
  
  	window openInWorldExtent: (self desiredDisplayExtent
  								+ (2 * window borderWidth)
  								+ (0 at window labelHeight)
  								* (1@(1/0.95))) rounded!

Item was changed:
  ----- Method: StackInterpreterSimulator>>primitiveDirectoryEntry (in category 'file primitives') -----
  primitiveDirectoryEntry
  	| name pathName array result |
  	name := self stringOf: self stackTop.
  	pathName := self stringOf: (self stackValue: 1).
  	
  	self successful ifFalse:
  		[^self primitiveFail].
  
+ 	array := FileSystem workingDirectory primLookupEntryIn: pathName name: name.
- 	array := FileDirectory default primLookupEntryIn: pathName name: name.
  	array == nil ifTrue:
  		[self pop: 3 thenPush: objectMemory nilObject.
  		^array].
  	array == #badDirectoryPath ifTrue:
  		[self halt.
  		^self primitiveFail].
  
  	result := self makeDirEntryName: (array at: 1) 
  		size: (array at: 1) size
  		createDate: (array at: 2) 
  		modDate: (array at: 3)
  		isDir: (array at: 4)  
  		fileSize: (array at: 5)
  		posixPermissions: (array at: 6)
  		isSymlink: (array at: 7).
  	self pop: 3.
  	self push: result!

Item was changed:
  ----- Method: StackInterpreterSimulator>>primitiveDirectoryLookup (in category 'file primitives') -----
  primitiveDirectoryLookup
  	| index pathName array result |
  	index := self stackIntegerValue: 0.
  	pathName := (self stringOf: (self stackValue: 1)).
  	
  	self successful ifFalse:
  		[^self primitiveFail].
  
+ 	array := FileSystem workingDirectory primLookupEntryIn: pathName index: index.
- 	array := FileDirectory default primLookupEntryIn: pathName index: index.
  
  	array == nil ifTrue:
  		[self pop: 3 thenPush: objectMemory nilObject.
  		^array].
  	array == #badDirectoryPath ifTrue:
  		["self halt."
  		^self primitiveFail].
  
  	result := self 
  		makeDirEntryName: (array at: 1) 
  		size: (array at: 1) size
  		createDate: (array at: 2) 
  		modDate: (array at: 3)
  		isDir: (array at: 4)  
  		fileSize: (array at: 5)
  		posixPermissions: (array at: 6)
  		isSymlink: (array at: 7).
  	self pop: 3 thenPush: result!

Item was changed:
  ----- Method: TParseNode>>emitCCommentOn:level: (in category 'C code generation') -----
  emitCCommentOn: aStream level: level
  	"Emit the transferred Smalltalk comments as C comments."
  
  	comment ifNotNil:
  		[comment isString ifTrue: [^self].	"safety catch"
  		 aStream cr.
  		 1 to: comment size do: [:index | 
  			aStream tab: level; nextPutAll: '/* '.
  			((comment at: index) findTokens: Character cr)
+ 				do: [:line| aStream nextPutAll: line trimBoth]
- 				do: [:line| aStream nextPutAll: line withBlanksTrimmed]
  				separatedBy: [aStream crtab: level; next: 3 put: Character space].
  			aStream nextPutAll: ' */'; cr].
  		 aStream cr]!

Item was changed:
  ----- Method: VMMaker class>>generateNewspeakCogVM (in category 'configurations') -----
  generateNewspeakCogVM
+ 	^ VMMaker
- 	^VMMaker
  		generate: CoInterpreter
+ 		and: StackToRegisterMappingCogit
+ 		with: #(#NewspeakVM true #MULTIPLEBYTECODESETS true)
+ 		to: 'oscogvm/nscogsrc' asFileReference fullName
+ 		platformDir: 'oscogvm/platforms' asFileReference fullName
+ 		including:
+ 			#(#AsynchFilePlugin #BMPReadWriterPlugin #BalloonEnginePlugin #BitBltSimulation #DSAPlugin #DropPlugin #FileCopyPlugin #FilePlugin #FloatArrayPlugin #FloatMathPlugin #InflatePlugin #JPEGReadWriter2Plugin #JPEGReaderPlugin #LargeIntegersPlugin #Matrix2x3Plugin #MiscPrimitivePlugin #NewsqueakIA32ABIPlugin #RePlugin #SecurityPlugin #SocketPlugin #SoundPlugin #SqueakSSLPlugin #SurfacePlugin #ThreadedIA32FFIPlugin #UUIDPlugin #UnixOSProcessPlugin #VMProfileLinuxSupportPlugin #VMProfileMacSupportPlugin #Win32OSProcessPlugin)	"Cogit chooseCogitClass"!
- 		and: StackToRegisterMappingCogit"Cogit chooseCogitClass"
- 		with: #(	NewspeakVM true
- 				MULTIPLEBYTECODESETS true)
- 		to: (FileDirectory default pathFromURI: 'oscogvm/nscogsrc')
- 		platformDir: (FileDirectory default pathFromURI: 'oscogvm/platforms')
- 		including:#(	AsynchFilePlugin BMPReadWriterPlugin BalloonEnginePlugin BitBltSimulation DSAPlugin DropPlugin
- 					FileCopyPlugin FilePlugin FloatArrayPlugin FloatMathPlugin InflatePlugin JPEGReadWriter2Plugin
- 					JPEGReaderPlugin LargeIntegersPlugin Matrix2x3Plugin MiscPrimitivePlugin NewsqueakIA32ABIPlugin
- 					RePlugin SecurityPlugin SocketPlugin SoundPlugin SqueakSSLPlugin SurfacePlugin ThreadedIA32FFIPlugin
- 					UUIDPlugin UnixOSProcessPlugin VMProfileLinuxSupportPlugin VMProfileMacSupportPlugin Win32OSProcessPlugin)!

Item was changed:
  ----- Method: VMMaker class>>generateNewspeakInterpreterVM (in category 'configurations') -----
  generateNewspeakInterpreterVM
+ 	^ VMMaker
- 	^VMMaker
  		generate: NewspeakInterpreter
+ 		to: 'oscogvm/nssrc' asFileReference fullName
+ 		platformDir: 'oscogvm/platforms' asFileReference fullName
+ 		including:
+ 			#(#AsynchFilePlugin #BMPReadWriterPlugin #BalloonEnginePlugin #BitBltSimulation #DSAPlugin #DropPlugin #FileCopyPlugin #FilePlugin #FloatArrayPlugin #FloatMathPlugin #InflatePlugin #JPEGReadWriter2Plugin #JPEGReaderPlugin #LargeIntegersPlugin #Matrix2x3Plugin #MiscPrimitivePlugin #NewsqueakIA32ABIPlugin #RePlugin #SecurityPlugin #SocketPlugin #SoundPlugin #SqueakSSLPlugin #SurfacePlugin #UUIDPlugin #UnixOSProcessPlugin #VMProfileLinuxSupportPlugin #VMProfileMacSupportPlugin #Win32OSProcessPlugin)!
- 		to: (FileDirectory default pathFromURI: 'oscogvm/nssrc')
- 		platformDir: (FileDirectory default pathFromURI: 'oscogvm/platforms')
- 		including:#(	AsynchFilePlugin BMPReadWriterPlugin BalloonEnginePlugin BitBltSimulation DSAPlugin DropPlugin
- 					FileCopyPlugin FilePlugin FloatArrayPlugin FloatMathPlugin InflatePlugin JPEGReadWriter2Plugin
- 					JPEGReaderPlugin LargeIntegersPlugin Matrix2x3Plugin MiscPrimitivePlugin NewsqueakIA32ABIPlugin
- 					RePlugin SecurityPlugin SocketPlugin SoundPlugin SqueakSSLPlugin SurfacePlugin
- 					UUIDPlugin UnixOSProcessPlugin VMProfileLinuxSupportPlugin VMProfileMacSupportPlugin Win32OSProcessPlugin)!

Item was changed:
  ----- Method: VMMaker class>>generateNewspeakStackVM (in category 'configurations') -----
  generateNewspeakStackVM
+ 	^ VMMaker
- 	^VMMaker
  		generate: StackInterpreter
+ 		with: #(#NewspeakVM true #MULTIPLEBYTECODESETS true)
+ 		to: 'oscogvm/nsstacksrc' asFileReference fullName
+ 		platformDir: 'oscogvm/platforms' asFileReference fullName
+ 		including:
+ 			#(#AsynchFilePlugin #BMPReadWriterPlugin #BalloonEnginePlugin #BitBltSimulation #DSAPlugin #DropPlugin #FileCopyPlugin #FilePlugin #FloatArrayPlugin #FloatMathPlugin #InflatePlugin #JPEGReadWriter2Plugin #JPEGReaderPlugin #LargeIntegersPlugin #Matrix2x3Plugin #MiscPrimitivePlugin #NewsqueakIA32ABIPlugin #RePlugin #SecurityPlugin #SocketPlugin #SoundPlugin #SurfacePlugin #SqueakSSLPlugin #ThreadedIA32FFIPlugin #UUIDPlugin #UnixOSProcessPlugin #VMProfileLinuxSupportPlugin #VMProfileMacSupportPlugin #Win32OSProcessPlugin)!
- 		with: #(NewspeakVM true MULTIPLEBYTECODESETS true)
- 		to: (FileDirectory default pathFromURI: 'oscogvm/nsstacksrc')
- 		platformDir: (FileDirectory default pathFromURI: 'oscogvm/platforms')
- 		including:#(	AsynchFilePlugin BMPReadWriterPlugin BalloonEnginePlugin BitBltSimulation DSAPlugin DropPlugin
- 					FileCopyPlugin FilePlugin FloatArrayPlugin FloatMathPlugin InflatePlugin JPEGReadWriter2Plugin
- 					JPEGReaderPlugin LargeIntegersPlugin Matrix2x3Plugin MiscPrimitivePlugin NewsqueakIA32ABIPlugin
- 					RePlugin SecurityPlugin SocketPlugin SoundPlugin SurfacePlugin SqueakSSLPlugin ThreadedIA32FFIPlugin
- 					UUIDPlugin UnixOSProcessPlugin VMProfileLinuxSupportPlugin VMProfileMacSupportPlugin Win32OSProcessPlugin)!

Item was changed:
  ----- Method: VMMaker class>>generateSqueakCogSistaVM (in category 'configurations') -----
  generateSqueakCogSistaVM
+ 	^ VMMaker
+ 		generate:
+ 			(Smalltalk
+ 				at:
+ 					([ :choices | choices at: (UIManager default chooseFrom: choices) ifAbsent: [ ^ self ] ]
+ 						value: #(#CoInterpreter #CoInterpreterMT)))
- 	^VMMaker
- 		generate: (Smalltalk at: ([:choices| choices at: (UIManager default chooseFrom: choices) ifAbsent: [^self]]
- 									value: #(CoInterpreter CoInterpreterMT)))
  		and: SistaStackToRegisterMappingCogit
+ 		to: 'oscogvm/sistasrc' asFileReference fullName
+ 		platformDir: 'oscogvm/platforms' asFileReference fullName
+ 		excluding: (InterpreterPlugin withAllSubclasses collect: [ :ea | ea name ])!
- 		to: (FileDirectory default pathFromURI: 'oscogvm/sistasrc')
- 		platformDir: (FileDirectory default pathFromURI: 'oscogvm/platforms')
- 		excluding: (InterpreterPlugin withAllSubclasses collect: [:ea| ea name])!

Item was changed:
  ----- Method: VMMaker class>>generateSqueakCogVM (in category 'configurations') -----
  generateSqueakCogVM
+ 	^ VMMaker
+ 		generate:
+ 			(Smalltalk
+ 				at:
+ 					([ :choices | choices at: (UIManager default chooseFrom: choices) ifAbsent: [ ^ self ] ]
+ 						value: #(#CoInterpreter #CoInterpreterMT)))
- 	^VMMaker
- 		generate: (Smalltalk at: ([:choices| choices at: (UIManager default chooseFrom: choices) ifAbsent: [^self]]
- 									value: #(CoInterpreter CoInterpreterMT)))
  		and: StackToRegisterMappingCogit
+ 		with: #(#MULTIPLEBYTECODESETS false #NewspeakVM false)
+ 		to: 'oscogvm/src' asFileReference fullName
+ 		platformDir: 'oscogvm/platforms' asFileReference fullName
+ 		including:
+ 			#(#ADPCMCodecPlugin #AsynchFilePlugin #BalloonEnginePlugin #B3DAcceleratorPlugin #BMPReadWriterPlugin #BitBltSimulation #BochsIA32Plugin #CroquetPlugin #DSAPlugin #DeflatePlugin #DropPlugin #FT2Plugin #FFTPlugin #FileCopyPlugin #FilePlugin #FloatArrayPlugin #FloatMathPlugin #GeniePlugin #HostWindowPlugin #IA32ABIPlugin #InternetConfigPlugin #JPEGReadWriter2Plugin #JPEGReaderPlugin #JoystickTabletPlugin #KlattSynthesizerPlugin #LargeIntegersPlugin #LocalePlugin #MIDIPlugin #MacMenubarPlugin #Matrix2x3Plugin #MiscPrimitivePlugin #Mpeg3Plugin #QuicktimePlugin #RePlugin #SecurityPlugin #SerialPlugin #SocketPlugin #SoundCodecPlugin #SoundGenerationPlugin #SoundPlugin #SqueakSSLPlugin #StarSqueakPlugin #ThreadedIA32FFIPlugin #UnixAioPlugin #UUIDPlugin #UnixOSProcessPlugin #Win32OSProcessPlugin #VMProfileLinuxSupportPlugin #VMProfileMacSupportPlugin)!
- 		with: #(	MULTIPLEBYTECODESETS false
- 				NewspeakVM false)
- 		to: (FileDirectory default pathFromURI: 'oscogvm/src')
- 		platformDir: (FileDirectory default pathFromURI: 'oscogvm/platforms')
- 		including:#(	ADPCMCodecPlugin AsynchFilePlugin BalloonEnginePlugin B3DAcceleratorPlugin
- 					BMPReadWriterPlugin BitBltSimulation BochsIA32Plugin CroquetPlugin DSAPlugin
- 					DeflatePlugin DropPlugin FT2Plugin FFTPlugin FileCopyPlugin FilePlugin FloatArrayPlugin
- 					FloatMathPlugin GeniePlugin HostWindowPlugin IA32ABIPlugin InternetConfigPlugin
- 					JPEGReadWriter2Plugin JPEGReaderPlugin JoystickTabletPlugin KlattSynthesizerPlugin
- 					LargeIntegersPlugin LocalePlugin MIDIPlugin MacMenubarPlugin Matrix2x3Plugin
- 					MiscPrimitivePlugin Mpeg3Plugin QuicktimePlugin RePlugin SecurityPlugin SerialPlugin
- 					SocketPlugin SoundCodecPlugin SoundGenerationPlugin SoundPlugin SqueakSSLPlugin StarSqueakPlugin
- 					ThreadedIA32FFIPlugin UnixAioPlugin UUIDPlugin UnixOSProcessPlugin
- 					Win32OSProcessPlugin VMProfileLinuxSupportPlugin VMProfileMacSupportPlugin)!

Item was changed:
  ----- Method: VMMaker class>>generateSqueakStackVM (in category 'configurations') -----
  generateSqueakStackVM
  	"No primitives since we can use those for the Cog VM"
  	^VMMaker
  		generate: StackInterpreter
+ 		to: (FileSystem workingDirectory directoryNamed: 'oscogvm/stacksrc') fullName
+ 		platformDir: (FileSystem workingDirectory directoryNamed: 'oscogvm/platforms') fullName
- 		to: (FileDirectory default directoryNamed: 'oscogvm/stacksrc') fullName
- 		platformDir: (FileDirectory default directoryNamed: 'oscogvm/platforms') fullName
  		excluding: (InterpreterPlugin withAllSubclasses collect: [:ea| ea name])!

Item was changed:
  ----- Method: VMMaker class>>machinesDirName (in category 'accessing') -----
  machinesDirName
+ 	^DirNames at: #machineType ifAbsent:[Smalltalk os platformName]!
- 	^DirNames at: #machineType ifAbsent:[SmalltalkImage current platformName]!

Item was changed:
  ----- Method: VMMaker>>buildCodeGeneratorForInterpreter: (in category 'generate sources') -----
  buildCodeGeneratorForInterpreter: getAPIMethods
  	"Answer the code generator for translating the interpreter."
  
  	| cg interpreterClass interpreterClasses structClasses apicg |
  	interpreterClasses := OrderedCollection new.
  
  	(cg := self createCodeGenerator) vmClass: (interpreterClass := self interpreterClass).
  
  	[interpreterClass ~~ VMClass] whileTrue:
  		[interpreterClasses addFirst: interpreterClass.
  		 interpreterClass := interpreterClass superclass].
  	
  	cg vmClass objectMemoryClass ifNotNil:
  		[:objectMemoryClass|
  		interpreterClass := objectMemoryClass.
  		[interpreterClass ~~ VMClass] whileTrue:
  			[interpreterClasses addFirst: interpreterClass.
  			 interpreterClass := interpreterClass superclass]].
  
  	interpreterClasses addFirst: VMClass.
  	interpreterClasses addAllLast: (self interpreterClass ancilliaryClasses copyWithout: cg vmClass objectMemoryClass).
  	structClasses := Set new.
  	interpreterClasses do: [:class| structClasses addAll: class ancilliaryStructClasses].
+ 	(Class superclassOrder: structClasses asArray) do:
- 	(ChangeSet superclassOrder: structClasses asArray) do:
  		[:structClass|
  		structClass initialize. ].
  
  	interpreterClasses do:
  		[:ic|
  		(ic respondsTo: #initializeWithOptions:)
  			ifTrue: [ic initializeWithOptions: optionsDictionary]
  			ifFalse: [ic initialize]].
  
+ 	(Class superclassOrder: structClasses asArray) do:
- 	(ChangeSet superclassOrder: structClasses asArray) do:
  		[:structClass|
  		cg addStructClass: structClass].
  
  	interpreterClasses do: [:ic| cg addClass: ic].
  
  	(getAPIMethods
  	and: [self interpreterClass needsCogit]) ifTrue:
  		[apicg := self buildCodeGeneratorForCogit: false.
  		 cg apiMethods: apicg selectAPIMethods].
  
  	^cg!

Item was changed:
  ----- Method: VMMaker>>configurationInfo (in category 'objects from disk') -----
  configurationInfo
  	"build a simple Array of the configuration information that would be 
  	 usefully saved for later reloading:- 
  		the list of internal & external plugins,
  		the flags,
  		the platform name,
  		the two major directory names,
  		bytePerWord
  		two flags indicating whether each directory is relative to the current directory or not.
  		the interpreter class name"
  	| isRelative makeRelative |
+ 	isRelative := [:pn| pn beginsWith: FileSystem workingDirectory pathName].
- 	isRelative := [:pn| pn beginsWith: FileDirectory default pathName].
  	makeRelative := [:pn|
  					(isRelative value: pn)
+ 						ifTrue: [pn allButFirst: FileSystem workingDirectory pathName size + 1]
- 						ifTrue: [pn allButFirst: FileDirectory default pathName size + 1]
  						ifFalse: [pn]].
  	^{ internalPlugins asArray.
  		externalPlugins asArray.
  		inline.
  		forBrowser.
  		platformName.
  		makeRelative value: self sourceDirectory pathName.
  		makeRelative value: self platformRootDirectory pathName.
  		self bytesPerWord.
  		isRelative value: self sourceDirectory pathName.
  		isRelative value: self platformRootDirectory pathName.
  		self interpreterClassName
  	  }!

Item was changed:
  ----- Method: VMMaker>>copyFileNamed:to: (in category 'private - copying files') -----
  copyFileNamed: srcName to: dstName 
  	| dstEntry srcEntry |
+ 	dstEntry := dstName asFileReference entry.
- 	dstEntry := FileDirectory directoryEntryFor: dstName.
  	dstEntry ifNotNil:[
+ 		srcEntry := srcName asFileReference entry.
- 		srcEntry := FileDirectory directoryEntryFor: srcName.
  		srcEntry ifNil:[^self couldNotOpenFile: srcName].
  		dstEntry modificationTime >= srcEntry modificationTime ifTrue:[^self].
  	].
  	logger show:'==> ', dstName; cr.
  	^self primitiveCopyFileNamed: srcName to: dstName !

Item was changed:
  ----- Method: VMMaker>>generateExportsFile (in category 'exports') -----
  generateExportsFile
  	"Store the exports on the given file"
  	| cg contents filePath fileStream |
  	cg := self createCodeGenerator.
  	cg vmClass: self interpreterClass.
  	contents := String streamContents:
  		[:s|
  		s
  			nextPutAll:'/* This is an automatically generated table of all builtin modules in the VM';
  			cr;
  			next: 3 put: Character space;
  			nextPutAll: (cg shortMonticelloDescriptionForClass: cg vmClass);
  			cr;
  			nextPutAll:' */';
  			cr.
  		s cr; nextPutAll:'extern sqExport vm_exports[];'.
  		s cr; nextPutAll: 'extern sqExport os_exports[];'.
  		self internalPluginsDo:[:cls|
  			s cr; nextPutAll: 'extern sqExport '; nextPutAll: cls moduleName; nextPutAll:'_exports[];'.
  		].
  		s cr.
  
  		s cr; nextPutAll:'sqExport *pluginExports[] = {'.
  		s crtab; nextPutAll:'vm_exports,'.
  		s crtab; nextPutAll: 'os_exports,'.
  		self internalPluginsDo:[:cls|
  			s crtab; nextPutAll: cls moduleName; nextPutAll:'_exports,'
  		].
  		s crtab; nextPutAll:'NULL'.
  		s cr; nextPutAll:'};'; cr].
  	filePath := self interpreterExportsFilePath.
+ 	(cg needToGenerateHeader: filePath asFileReference basename file: filePath contents: contents) ifTrue:
- 	(cg needToGenerateHeader: (FileDirectory baseNameFor: filePath) file: filePath contents: contents) ifTrue:
  		[[fileStream := VMMaker forceNewFileNamed: filePath] 
  			on: FileDoesNotExistException 
  			do:[^self couldNotOpenFile: filePath].
  		 fileStream nextPutAll: contents; close]!

Item was changed:
  ----- Method: VMMaker>>needsToRegenerateCogitFile (in category 'generate sources') -----
  needsToRegenerateCogitFile
  "check the timestamp for the relevant classes and then the timestamp for the interp.c file if it already exists. Return true if the file needs regenerating, false if not"
  
  	| cogitClass cogitClasses tStamp fstat |
  	cogitClass := self cogitClass.
  	cogitClasses := cogitClass withAllSuperclasses copyUpThrough: Cogit.
  	cogitClasses addAllLast: cogitClass ancilliaryClasses.
  	tStamp := cogitClasses inject: 0 into: [:tS :cl| tS max: cl timeStamp].
  	cogitClasses do:
  		[:c|
  		tStamp := c ancilliaryStructClasses inject: tStamp into: [:tS :cl| tS max: cl timeStamp]].
  
  	"don't translate if the file is newer than my timeStamp"
  	fstat := self coreVMDirectory entryAt: cogitClass sourceFileName ifAbsent:[nil].
+ 	fstat ifNotNil:[ tStamp < fstat modificationTime asSeconds ifTrue:
- 	fstat ifNotNil:[tStamp < fstat modificationTime ifTrue:
  		[^self confirm: 'The ', cogitClass printString, ' classes have not been modified since\ the source file was last generated.\Do you still want to regenerate it?' withCRs]].
  	^true
  !

Item was changed:
  ----- Method: VMMaker>>needsToRegenerateInterpreterFile (in category 'initialize') -----
  needsToRegenerateInterpreterFile
  "check the timestamp for the relevant classes and then the timestamp for the interp.c file if it already exists. Return true if the file needs regenerating, false if not"
  
  	| classes tStamp fstat |
  	classes := self interpreterClass withAllSuperclasses copyUpTo: VMClass.
  	self interpreterClass objectMemoryClass ifNotNil:
  		[:objectMemoryClass|
  		classes addAllLast: (objectMemoryClass  withAllSuperclasses copyUpTo: VMClass)].
  	classes copy do:
  		[:class| classes addAllLast: class ancilliaryClasses].
  	classes copy do:
  		[:class| classes addAllLast: class ancilliaryStructClasses].
  	tStamp := classes inject: 0 into: [:tS :cl| tS max: cl timeStamp].
  
  	"don't translate if the file is newer than my timeStamp"
  	fstat := self coreVMDirectory entryAt: self interpreterFilename ifAbsent:[nil].
+ 	fstat ifNotNil:[ tStamp < fstat modificationTime asSeconds ifTrue:
- 	fstat ifNotNil:[tStamp < fstat modificationTime ifTrue:
  		[^self confirm: 'The interpreter classes have not been modified since\ the interpreter file was last generated.\Do you still want to regenerate their source file?' withCRs]].
  	^true
  !

Item was changed:
  ----- Method: VMMaker>>platformRootDirectory (in category 'source directories') -----
  platformRootDirectory
  	"return the directory where we should find all platform's sources"
+ 
+ 	(platformRootDirName ifNil: [ self class platformsDirName ]) asFileReference isDirectory
+ 		ifFalse: [ 
+ 			"The supposed directory for the platforms code does not  
- 	(FileDirectory default
- 			directoryExists: (platformRootDirName
- 					ifNil: [self class platformsDirName]))
- 		ifFalse: ["The supposed directory for the platforms code does not  
  			exist."
+ 			^ self couldNotFindDirectory: 'the platform code tree' ].
+ 	^ FileSystem workingDirectory directoryNamed: (platformRootDirName ifNil: [ self class platformsDirName ])!
- 			^ self couldNotFindDirectory: 'the platform code tree'].
- 	^ FileDirectory default
- 		directoryNamed: (platformRootDirName
- 				ifNil: [self class platformsDirName])!

Item was changed:
  ----- Method: VMMaker>>platformRootDirectoryName: (in category 'source directories') -----
  platformRootDirectoryName: aString
  	"set the directory where we should find all platform's sources
  	There really ought to be plausible sanity checks done here"
+ 
  	platformRootDirName := aString.
+ 	aString asFileReference isDirectory
+ 		ifFalse: [ 
+ 			self couldNotFindDirectory: aString.
+ 			^ false ].
- 	(FileDirectory default directoryExists: aString) ifFalse:[self couldNotFindDirectory: aString. ^false].
  	self reinitializePluginsLists.
+ 	^ true!
- 	^true!

Item was changed:
  ----- Method: VMMaker>>sourceDirectory (in category 'target directories') -----
  sourceDirectory
  	| fd |
+ 	fd := FileSystem workingDirectory directoryNamed: (sourceDirName
- 	fd := FileDirectory default directoryNamed: (sourceDirName
  		ifNil: [self class sourceDirName, self vmBitnessString]).
  	fd assureExistence.
  	^ fd!

Item was changed:
  ----- Method: VMMaker>>sourceDirectoryName: (in category 'target directories') -----
  sourceDirectoryName: aString
  	"Sanity check really ought to be added, This is the root directory for where the sources will be WRITTEN"
+ 
  	sourceDirName := aString.
+ 	aString asFileReference ensureDirectory.
- 	(aString first == $.
- 		ifTrue: [FileDirectory default directoryNamed: aString]
- 		ifFalse: [FileDirectory on: aString]) assureExistence.
  	self changed: #sourceDirectory.
+ 	^ true!
- 	^true!

Item was changed:
  ----- Method: VMMakerTool>>loadConfig (in category 'configurations') -----
  loadConfig
  	| fileResult file |
+ 	fileResult := (StandardFileMenu oldFileMenu: FileSystem workingDirectory withPattern: '*.config')
- 	fileResult := (StandardFileMenu oldFileMenu: FileDirectory default withPattern: '*.config')
  				startUpWithCaption: 'Select VMMaker configuration...'.
  	fileResult
  		ifNotNil: [file := fileResult directory fullNameFor: fileResult name.
  			[vmMaker := VMMaker forConfigurationFile: file.
  			vmMaker logger: logger.
  			vmMaker platformDirectory]
  				on: Error
  				do: [self inform: 'Possible problem with path settings or platform name?'].
  			self updateAllViews]!

Item was changed:
  ----- Method: VMMakerTool>>saveConfig (in category 'configurations') -----
  saveConfig
  
  	"write info about the current configuration to a file."
  	| fileResult file |
+ 	fileResult := (StandardFileMenu newFileMenu: FileSystem workingDirectory withPattern: '*.config')
- 	fileResult := (StandardFileMenu newFileMenu: FileDirectory default withPattern: '*.config')
  		startUpWithCaption: 'Save VMMaker configuration...'.
  	fileResult ifNotNil: [
  		('*.config' match: fileResult name)
  			ifFalse: [fileResult name: (fileResult name, '.config')].
  		file := fileResult directory fullNameFor: fileResult name.
  		vmMaker saveConfigurationTo: file].
  !



More information about the Vm-dev mailing list