[Pkg] Rio: File-Kernel-kph.15.mcz

squeak-dev-noreply at lists.squeakfoundation.org squeak-dev-noreply at lists.squeakfoundation.org
Mon Mar 2 04:41:52 UTC 2009


A new version of File-Kernel was added to project Rio:
http://www.squeaksource.com/Rio/File-Kernel-kph.15.mcz

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

Name: File-Kernel-kph.15
Author: kph
Time: 2 March 2009, 4:41:46 am
UUID: 6fe5f618-06e4-11de-a0af-000a95edb42a
Ancestors: File-Kernel-kph.14

+ Better instanciation code all round
+ handle line endings


=============== Diff against File-Kernel-kph.14 ===============

Item was changed:
  ----- Method: FileExecutive>>basicReader: (in category 'as yet unclassified') -----
  basicReader: aFile
  
+ 	^ aFile fileStream open: aFile forWrite: false!
- 	^ self class fileStreamClass new open: aFile forWrite: false!

Item was changed:
  ----- Method: FileExecutive>>toDirLocal:addAllLocal:relativeTo: (in category 'local/remote file copy') -----
  toDirLocal: aDir addAllLocal: someFD relativeTo: aBaseDir
  
  	| map overwrite dest |
  
+ 	overwrite := FileNotification isOverwrite.
- 	overwrite := FileNotification signal isOverwrite.
  
  	map := self toDir: aDir mkpathAll: someFD relativeTo: aBaseDir.
  	
  	^ map collect: [ :ea | 
  		dest := ea second.
  		(dest isDirectory not and: [ overwrite or: [ dest exists not ] ])
  			ifTrue: [ 
  				self copyLocalFile: ea first toLocalFile: dest 
  		].
  	
  	dest
  	].
  	
  	!

Item was changed:
  ----- Method: FileExecutive>>root (in category 'as yet unclassified') -----
  root
  
+ 	^ self class dirClass executive: self value: self rootString!
- 	^ self class makeNew: self class dirClass from: self rootString!

Item was changed:
  ----- Method: FileExecutive>>mkpath: (in category 'as yet unclassified') -----
+ mkpath: aDIr
- mkpath: aRio
  
+ 	aDIr isDirectory ifTrue: [ ^self ].
+ 	aDIr parent mkpath.
+ 	self createDirectory: aDIr.  !
- 	aRio isDirectory ifTrue: [ ^self ].
- 	aRio parent mkpath.
- 	self createDirectory: aRio.  !

Item was changed:
  ----- Method: FileLocalExecutive>>createDirectory: (in category 'executive actions') -----
+ createDirectory: aDir
- createDirectory: aRio
  	 
+ 	^ self primCreateDirectory: aDir asVmPathName  !
- 	^ self primCreateDirectory: aRio asVmPathName  !

Item was added:
+ ----- Method: FileLocalExecutive>>print:on: (in category 'pretending') -----
+ print: aFileKernel on: str
+ 
+ 	str << $( << aFileKernel class name << ' new: ''' << aFileKernel value << ''')'
+ 	
+ !

Item was changed:
  ----- Method: FileLocalExecutive>>defaultDirectory (in category 'accessing') -----
  defaultDirectory
  
+ 	^ self class dirClass executive: self value: defaultDirectory  !
- 	^ defaultDirectory asDirectory!

Item was changed:
  ----- Method: FileKernel>>fileName: (in category 'accessing') -----
  fileName: newFileName
   
  	self splitToPathAndName: [ :dirPath :fileName | 
+ 		value := executive importValue: dirPath.
+ 		self pathJoin: newFileName.
- 		value := executive importValue: ((self newFrom: dirPath) pathJoin: newFileName) asString
   	].!

Item was changed:
  ----- Method: FileLocalExecutive>>getImageDirectory (in category 'executive actions') -----
  getImageDirectory
  
+  	^ self getImageFile parent !
-  	^ (self dirClass executive: self value: self primImagePath) parent !

Item was added:
+ ----- Method: FileNotification>>executive (in category 'accessing') -----
+ executive 
+ 
+ 	^ executive ifNil: [ FileLocalExecutive local ]!

Item was added:
+ ----- Method: FileExecutive>>lineEndConvention (in category 'instanciation') -----
+ lineEndConvention
+ 
+ 	^ #lf!

Item was changed:
  ----- Method: FileLocalDosExecutive>>getTempDirectory (in category 'as yet unclassified') -----
  getTempDirectory
  
+  	^ self class dirClass new: 'C:\WINDOWS\TEMP\'!
-  	^ self dirClass new: 'C:\WINDOWS\TEMP\'!

Item was added:
+ ----- Method: FileExecutive>>newOfClass:from: (in category 'instanciation') -----
+ newOfClass: aClass from: aPathString 
+  	"this is the core instanciation method"
+ 	
+ 	| voted new |
+ 	
+ 	"take a vote, if anyone wants to be the executive for this path"
+ 	voted := self class classForPath: aPathString.
+ 
+ 	voted := self checkVoted: voted.
+ 
+ 	new := voted 	ifNotNil: [ voted makeNew: aClass from: aPathString ]		
+ 					ifNil: [ aClass executive: self value: aPathString ].
+ 
+ 	^ new lineEndConvention: self lineEndConvention; yourself!

Item was added:
+ ----- Method: FileLocalExecutive class>>local (in category 'accessing current') -----
+ local
+ 
+ 	^ Local 	
+ !

Item was added:
+ ----- Method: SocketStream>>lineEndConvention: (in category '*file-kernel') -----
+ lineEndConvention: aSymbol
+ 	"dummy for compat with MultiByteCharacterStream"
+ 	
+ 	!

Item was changed:
  FileExecutive subclass: #FileLocalExecutive
  	instanceVariableNames: 'rootString root defaultDirectory'
+ 	classVariableNames: 'Dynamic Fixed Local'
- 	classVariableNames: 'Current Test'
  	poolDictionaries: ''
  	category: 'File-Kernel'!
  
  !FileLocalExecutive commentStamp: 'kph 4/17/2007 19:25' prior: 0!
  Introducing the idea that Rio's exist in the context of their 'physical container', we have the RioLocalFileSystem as the primary container which provides the file system interface, also known as the 'executive'.
  
  On unix there is one executive for the whole system. On dos there is one executive per volume. This approach also supports the notion of files within archives and files on remote servers.
  
  On startup, having a formal model of the host filesystem allows us to keep a current and previous instance introducing the possibility for migrating Rio's on startup when the image has been moved. For example C:/ could be replaced with /mnt/hda1 thus attempting to make images properly portable. (experimental idea)
  
  !

Item was changed:
  ----- Method: FileKernel class>>new: (in category 'as yet unclassified') -----
  new: aPathOrFile
  
+ 	^ self fromString: aPathOrFile asString!
- 	"the preferred generic instanciation method, 
- 	will call the correct specific instanciation method on the correct class"
- 
- 	(aPathOrFile isKindOf: FileKernel) ifTrue: [ ^ aPathOrFile copy ].
- 	                                                                                                            	
- 	^ self defaultExecutive current class newDirectoryFrom: aPathOrFile!

Item was changed:
  ----- Method: FileLocalExecutive class>>initialize (in category 'class initialization') -----
  initialize
  
  	Smalltalk addToStartUpList: self after: Delay.
+ 	Local := self newForThisPlatform initializeDefault.
- 	Current := self newForThisPlatform.
- 	Current initializeDefault.
  	!

Item was added:
+ ----- Method: FileKernel>>linearRelativeTo: (in category 'accessing') -----
+ linearRelativeTo: aDirectoryOrFile
+  	| tmp |
+ 	self full = aDirectoryOrFile full ifTrue: [ ^ Directory new: '' ].
+ 
+ 	tmp := (self parent linearRelativeTo: aDirectoryOrFile) / self fileName.	
+ 	
+ 	^tmp
+ 	 !

Item was added:
+ ----- Method: FileKernel>>asUrl (in category 'coercing') -----
+ asUrl
+ 
+ 	^ executive toUrl: self!

Item was added:
+ ----- Method: FileLocalExecutive class>>dynamic (in category 'accessing current') -----
+ dynamic
+ 
+ 	^ Dynamic ifNil: [ Local ]
+  	
+ !

Item was added:
+ ----- Method: FileKernel class>>fromString: (in category 'as yet unclassified') -----
+ fromString: aPathString
+ 		                                                                                                        
+ 	^ self localExecutive newOfClass: self from: aPathString 
+ 	!

Item was added:
+ ----- Method: FileKernel class>>localExecutive (in category 'as yet unclassified') -----
+ localExecutive
+ 
+ 	^ FileLocalExecutive dynamic currentExecutive!

Item was added:
+ ----- Method: FileNotification class>>currentExecutive (in category 'queries') -----
+ currentExecutive
+ 
+ 	^ self new signal executive!

Item was changed:
  ----- Method: FileLocalExecutive>>deleteFile: (in category 'executive actions') -----
+ deleteFile: aFile	
- deleteFile: aRio
- 	
  	"Delete the file of the given name if it exists.
  	If the first deletion attempt fails do a GC to force finalization of any lost references. ar 3/21/98 17:53"
  		 
  	self retryWithGC: [
+ 		self primDeleteFileNamed: aFile asVmPathName ]
- 		self primDeleteFileNamed: aRio asVmPathName ]
  		until:[:result| result notNil]
+ 		forFileNamed: aFile.
- 		forFileNamed: aRio.
  		
+ 	aFile statIsNowInvalid!
- 	aRio statIsNowInvalid!

Item was added:
+ ----- Method: FileKernel>>as: (in category 'comparison+legacy enabling') -----
+ as: someOtherClass
+ 
+ 	^ someOtherClass basicNew copyFrom: self
+ !

Item was added:
+ ----- Method: FileExecutive>>print:on: (in category 'printing') -----
+ print: aFileKernel on: str
+ 
+ 	str << '(''' << aFileKernel asUrl asString << ((aFileKernel isKindOf: (self class dirClass)) ifFalse:[ ''' asFile)' ] ifTrue: [ ''' asDirectory)' ])!

Item was changed:
  ----- Method: FileKernel class>>new (in category 'as yet unclassified') -----
  new
  
+ 	^ self error: 'use new:'!
- 	^ self new: '' !

Item was added:
+ ----- Method: FileKernel>>fileStream (in category 'public file') -----
+ fileStream
+ 
+ 	^ FileStream concreteStream new
+ 			lineEndConvention: lineEndConvention
+ 			yourself !

Item was changed:
  ----- Method: FileExecutive>>basicWriter: (in category 'as yet unclassified') -----
+ basicWriter: aFile
+ 	aFile statIsNowInvalid.
- basicWriter: aRio
- 	aRio statIsNowInvalid.
  
+ 	^ aFile fileStream open: aFile forWrite: true 
- 	^ self class fileStreamClass new open: aRio forWrite: true 
  	!

Item was added:
+ ----- Method: FileLocalExecutive>>in:select: (in category 'fs migration') -----
+ in: aDir select: selectBlock
+ 
+ 	^ self in: aDir excluding: #('.DS_Store' '__MACOSX') select: selectBlock
+ !

Item was changed:
  ----- Method: FileKernel class>>thisImage (in category 'as yet unclassified') -----
  thisImage
  
+ 	^ self localExecutive getImageFile!
- 	^ self new: self defaultExecutive current primImagePath.!

Item was changed:
  ----- Method: FileLocalExecutive class>>performStartUpMigration (in category 'image start up ') -----
  performStartUpMigration
   	| old |
  	
+ 	old := Local.
+ 	Local := self newForThisPlatform initializeDefault.
- 	old := self current.
- 	Current := self newForThisPlatform.
- 	Current initializeDefault.
  
+ 	old migrateFileSystemTo: Local.!
- 	old migrateFileSystemTo: Current!

Item was changed:
  Object subclass: #FileKernel
+ 	instanceVariableNames: 'executive value stat lineEndConvention'
- 	instanceVariableNames: 'executive value stat'
  	classVariableNames: 'TestFileSystem'
  	poolDictionaries: ''
  	category: 'File-Kernel'!
  
+ !FileKernel commentStamp: 'kph 3/1/2009 00:13' prior: 0!
+ The minimum File/Directory functionality required to support a kernel image
+ is implemented here, thus making File-Base etc unloadable.
- !FileKernel commentStamp: 'kph 11/2/2008 22:50' prior: 0!
- The minimum Rio functionality required to support a kernel image
- is implemented here, thus making the rest of rio unloadable.
  
+ Local file instanciation in File-Base is 'file' asFile, however asFIle/asDirectory are not included in File-Kernel in order to avoid stepping upon other packages, and for simplicity. To instanciate a local file or directory reference, FileKernel new: aString, is "the" way.
- Recursive querying via #select: is available however the selectBlock is passed a raw entryArray, rather than a RioStat instance. This is not intended to be used extensively but is needed as a minimum for #isFile/#isDirectory.
   
  If either #reader or #writer should fail RioKernel returns a nil, 
  
  A functionally complete interface to the parts of the fileName is available as follows:
  getter - splitToBaseVersionAndExt: [ :b :v :e |  ]
  setter - #base: <nil or newName> version: <nil or newVersion> ext: <nil or new ext>
  
  Interface for file versions is available via:
  #versions - returns a SortedCollection of the version numbers available for this rio
  #latestVersion - returns a rio for the latest version of the current rio in the versions list
  #nextVersion - returns a rio for the latest + 1 version of the current rio.
  
  Rio's may be included in the concatenation of strings
  
  RioKernel file copyTo: does a binary stream to stream copy, without a progress bar.
  Rio's file copyTo: honours the setting of the Rio's binary mode, and displays a progress bar.
  
  instVars
  ---------
  value - internal (to Rio) holds the path!

Item was added:
+ ----- Method: FileExecutive>>checkVoted: (in category 'instanciation') -----
+ checkVoted: voted
+ 
+ 	"alternative local executives may override this to rig the voting"
+ 	
+ 	^ voted
+ 
+ 	!

Item was changed:
  ----- Method: FileKernel>>printOn: (in category 'printing') -----
  printOn: str
  
+ 	self executive print: self on: str!
- 	str << $( << self class name << ' new: ''' << value << ''')'
- 	
- !

Item was changed:
  ----- Method: FileKernel>>/ (in category 'as yet unclassified') -----
  / morePath
  
+  	^ self copy pathJoin: morePath!
-  	^ self newFrom: (self pathJoin: morePath)!

Item was added:
+ ----- Method: FileLocalExecutive class>>platformName (in category 'image start up ') -----
+ platformName
+ 
+ 	^ SmalltalkImage current platformName asLegalSelector capitalized!

Item was added:
+ ----- Method: FileLocalExecutive>>startAt:recursively:select:excluding:into: (in category 'executive actions') -----
+ startAt: aDir recursively: beRecursive select: selectBlock excluding: xList into: results 
+ 
+ 	"Return a collection of rio's selected by passing
+ 	the directoryEntry array to the selectBlock.
+ 	
+ 	The KernelRio implemetation of setStatFromEntryArray: 
+ 	does not populate these rios with stat data.
+ 	Rio's more verbose implementation does.
+ 
+ 	This can be called with startAt: aString, but if so beRecursive must be false.
+ 		
+ 	See primLookupEntryIn:index: for further details."
+ 
+ 	| index entryArray entry isDir fName |
+ 
+ 	index := 1.
+ 
+ 	[ (entryArray := self primLookupEntryIn: aDir asVmPathName index: index) notNil ] 
+ 		whileTrue: [
+ 			#badDirectoryPath = entryArray ifTrue: [
+ 				^ results "(InvalidDirectoryError pathName: aDir value) signal" ].
+ 
+ 				isDir := entryArray at: 4.
+ 				fName := entryArray at: 1.
+ 				
+ 				(xList includes: fName) ifFalse: [ 
+ 					entry := ((isDir ifTrue: [ self class dirClass ] ifFalse: [ self class fileClass ]) 
+ 						executive: self value: aDir asString) 
+ 							pathJoin: fName;
+ 							setStatFromDir: aDir andEntryArray:entryArray;
+ 							yourself.
+ 					
+ 					(selectBlock value: entry) ifTrue: [ results add: entry ].	
+ 						
+ 					(beRecursive and: [ isDir ]) 
+ 						ifTrue: [ 
+ 							self 
+ 								startAt: entry
+ 								recursively: beRecursive 
+ 								select: selectBlock
+ 								excluding: xList
+ 								into: results   
+ 						].	
+ 				].
+ 			index := index + 1
+ 		].
+ 	
+ 	^ results!

Item was added:
+ ----- Method: FileLocalExecutive>>newDirectoryFrom: (in category 'accessing') -----
+ newDirectoryFrom: aPath!

Item was changed:
  ----- Method: FileLocalExecutive class>>makeNew:from: (in category 'as yet unclassified') -----
  makeNew: aClass from: path
  
  	| str |
  	
  	str := (path beginsWith: 'file:///') ifTrue: [ (path allButFirst: 7) unescapePercents ] ifFalse: [ path ].
  
+ 	^ aClass executive: aClass localExecutive value: str !
- 	^ aClass executive: self current value: str !

Item was added:
+ ----- Method: FileLocalDosExecutive>>lineEndConvention (in category 'as yet unclassified') -----
+ lineEndConvention
+ 
+ 	^ #crlf!

Item was changed:
  Notification subclass: #FileNotification
+ 	instanceVariableNames: 'isOverwrite executive'
- 	instanceVariableNames: 'isOverwrite'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'File-Kernel'!

Item was changed:
  ----- Method: FileKernel>>parent (in category 'accessing') -----
  parent
  
  	"note that the parent of root is the file system 'executive' "
  	
  	^self isRoot ifTrue: [ executive ]
+  				ifFalse: [ executive class dirClass executive: executive value: self full path ]
-  				ifFalse: [ executive dirClass executive: executive value: self full path ]
  	!

Item was changed:
  ----- Method: FileLocalExecutive class>>newForThisPlatform (in category 'image start up ') -----
  newForThisPlatform
  
+ 	^ self perform: ('newFor', self platformName) asSymbol!
- 	^ self perform: ('newFor', self platform) asSymbol!

Item was added:
+ ----- Method: FileExecutive>>in:excluding:select: (in category 'as yet unclassified') -----
+ in: aDir excluding: xList select: selectBlock
+ 
+ 	^ self 
+ 		startAt: aDir
+ 		recursively: aDir isRecursive 
+ 		select: selectBlock 
+ 		excluding: xList
+ 		into: (OrderedCollection new: 10)
+ !

Item was added:
+ ----- Method: FileNotification>>executive: (in category 'accessing') -----
+ executive: anObject
+ 
+ 	executive := anObject.
+ 	self resume: self.!

Item was changed:
  ----- Method: FileKernel>>select: (in category 'enumeration') -----
  select: selectBlock
  
  	"select: returns an empty result if the rio is not a valid directory."
  
+ 	^ executive in: self  select: selectBlock!
- 	^ executive in: self select: selectBlock!

Item was added:
+ ----- Method: FileLocalExecutive>>lineEndConvention (in category 'executive actions') -----
+ lineEndConvention
+ 
+ 	^ #lf!

Item was added:
+ ----- Method: Object>>isFileOrDirectory (in category '*file-kernel') -----
+ isFileOrDirectory
+ 
+ 	^ false!

Item was changed:
  ----- Method: FileLocalExecutive>>untrustedDirectory (in category 'executive actions') -----
  untrustedDirectory
  
+  	^ self class dirClass new: (SecurityManager default primUntrustedUserDirectory)
-  	^ self dirClass new: (SecurityManager default primUntrustedUserDirectory)
  	 !

Item was added:
+ ----- Method: FileExecutive class>>classForPath: (in category 'as yet unclassified') -----
+ classForPath: aPath
+ 
+ 	| executiveClass winner priority |
+ 	
+ 	winner := 0.
+ 	executiveClass := nil.
+ 	
+ 	FileExecutive allSubclassesDo: [ :c | 
+ 		priority := c canInstanciateFrom: aPath.
+ 		priority > winner ifTrue: [ 	winner := priority. 
+ 									executiveClass := c ] ].
+ 	
+ 	^ executiveClass !

Item was added:
+ ----- Method: FileLocalExecutive>>pretendDuring: (in category 'pretending') -----
+ pretendDuring: aBlock
+ 
+ 	"In rare circumstances we want to handle a list of dos paths while in fact we are a unix box,
+ 	lets say we were compiling a script to be remotely distributed to DOS box.
+ 	
+ 	This technique also helps with testing various filesystems.
+ 	
+ 	We pop the notification in to the Dynamic slot, the only call it knows is #currentExecutive
+ 	Within the block, a call to currentExecutive, signals, and returns self.
+ 	
+ 	We 'ensure:' everything returns to normal when the block exits, if you need to do this
+ 	manually, then FileNotification will return fixedExecutive currentExecutive by default.
+ 	
+ 	"
+ 	
+ 	| tmp |
+ 	
+ 	[ 
+ 		tmp := Dynamic.
+ 			Dynamic := FileNotification.
+ 	
+ 		[ aBlock value ] on: FileNotification do: [ :ex | ex executive: self ]
+ 	
+ 	] ensure: [ Dynamic := tmp ]!

Item was changed:
  ----- Method: FileLocalExecutive>>maxFileNameLength (in category 'misc') -----
  maxFileNameLength
  
   ^ (self class respondsTo: #maxFileNameLength) 
  	ifTrue: [ self class maxFileNameLength ]
+ 	ifFalse: [ self class perform: ('maxFileNameLengthOn', self class platformName) asSymbol ]!
- 	ifFalse: [ self class perform: ('maxFileNameLengthOn', self class platform) asSymbol ]!

Item was added:
+ ----- Method: FileNotification class>>isOverwrite (in category 'queries') -----
+ isOverwrite
+ 
+ 	^ self new signal isOverwrite!

Item was changed:
  ----- Method: FileExecutive>>dir:mkpath:relativeTo: (in category 'as yet unclassified') -----
  dir: aDir mkpath: aFileOrDir relativeTo: aBaseDirectory
  	
  	| newFD |
  	
+ 	newFD := aBaseDirectory ifNil: [ aDir / aFileOrDir fileName ]
- 	newFD := aBaseDirectory ifNil: [ (aDir / aFileOrDir fileName) asFile ]
  				    		 	 ifNotNil: [ aDir / (aFileOrDir linearRelativeTo: aBaseDirectory) ].
  
   	aFileOrDir isDirectory ifTrue: [ newFD mkpath ]. 
  	aFileOrDir isFile ifTrue: [ newFD parent mkpath ].
  	
  	^ newFD!

Item was changed:
  ----- Method: FileExecutive>>in:select: (in category 'as yet unclassified') -----
  in: aDir select: selectBlock
  
+ 	^ self in: aDir excluding: #() select: selectBlock
- 	^ self 
- 		startAt: aDir
- 		recursively: aDir isRecursive 
- 		select: selectBlock 
- 		into: (OrderedCollection new: 50)
  !

Item was changed:
  ----- Method: FileLocalExecutive>>getTempDirectory (in category 'executive actions') -----
  getTempDirectory
  
+  	^ self class dirClass new: '/tmp'!
-  	^ self dirClass new: '/tmp'!

Item was changed:
  ----- Method: FileLocalExecutive>>tempDirectory (in category 'executive actions') -----
  tempDirectory
  
+  	^ self class dirClass new: '/tmp'!
-  	^ self dirClass new: '/tmp'!

Item was added:
+ ----- Method: FileKernel>>split (in category 'private') -----
+ split
+ 	
+ 	| parent |
+  	
+ 	self value isEmpty ifTrue: [ ^ Array new ].
+ 	
+ 	self splitToPathAndName: [ :p :n |
+ 		parent := self newFrom: p.
+  
+ 		(parent = self) ifTrue: [ ^ Array with: (self value allButLast) ].
+ 		 
+ 		^ parent split copyWith: n
+ 	]
+ !

Item was added:
+ ----- Method: FileLocalExecutive>>getImageFile (in category 'executive actions') -----
+ getImageFile
+ 
+  	^ self class fileClass executive: self value: self primImagePath!

Item was added:
+ ----- Method: FileExecutive>>currentExecutive (in category 'case-sensitivity') -----
+ currentExecutive
+ 
+ 	"Dont call this, instead call, FileExecutive dynamic currentExecutive"
+ 	
+ 	^ self
+ 	
+  !

Item was changed:
  ----- Method: FileKernel>>pathJoin: (in category 'private') -----
  pathJoin: morePath
  
+ 	value := (executive isRoot: value) 
+ 		ifTrue: [ value , morePath asString ]
+ 		ifFalse: [ value isEmpty 
+ 					ifTrue: [ morePath asString ]
+ 					ifFalse: [ self value, '/', morePath asString ]]
- 	 (executive isRoot: value) ifTrue: [ ^ value , morePath asString ].
- 	
- 	 ^value isEmpty ifTrue: [ morePath asString ]
- 					ifFalse: [ self value, executive pathDelimiter, morePath asString ].
  !

Item was added:
+ ----- Method: FileKernel>>isFileOrDirectory (in category 'testing') -----
+ isFileOrDirectory
+ 
+ 	^true!

Item was changed:
  ----- Method: FileLocalDosExecutive class>>canInstanciateFrom: (in category 'as yet unclassified') -----
  canInstanciateFrom: aString
  
+ 	^ (#( 'file:///#:*'  '#:*' 'file:///#%3A*') anySatisfy: [ :m | m match: aString ]) ifTrue: [ 100 ] ifFalse: [ 0 ]
- 	^ (('file:///#:*' match: aString) or: [ '#:*' match: aString ]) ifTrue: [ 100 ] ifFalse: [ 0 ]
  	
  	!

Item was added:
+ ----- Method: FileKernel>>lineEndConvention: (in category 'file copy') -----
+ lineEndConvention: aSymbol
+ 	lineEndConvention := aSymbol!

Item was removed:
- ----- Method: FileKernel class>>newFileFrom: (in category 'as yet unclassified') -----
- newFileFrom: aPath
- 	                                                                                                            	
- 	^ self defaultExecutive current class newFileFrom: aPath!

Item was removed:
- ----- Method: FileExecutive class>>newDirectoryFrom: (in category 'as yet unclassified') -----
- newDirectoryFrom: aString
- 
- 	^ (self instanciatorFrom: aString) makeNew: self dirClass from: aString
-     !

Item was removed:
- ----- Method: FileLocalDosExecutive class>>instanciatorFrom: (in category 'as yet unclassified') -----
- instanciatorFrom: aString
- 
- 	"we being a dos file system have been asked to instancate a url, if that returns a FileLocalExecutive
- 	we butt in"
- 	
- 	^ (super instanciatorFrom: aString)!

Item was removed:
- ----- Method: FileKernel class>>fileStreamClass (in category 'as yet unclassified') -----
- fileStreamClass
- 
- 	^ FileStream concreteStream!

Item was removed:
- ----- Method: FileLocalExecutive class>>platform (in category 'image start up ') -----
- platform
- 
- 	^ SmalltalkImage current platformName asLegalSelector capitalized!

Item was removed:
- ----- Method: String>>asFile (in category '*file-kernel') -----
- asFile
- 
- 	^ FileKernel newFileFrom: self!

Item was removed:
- ----- Method: FileExecutive class>>instanciatorFrom: (in category 'as yet unclassified') -----
- instanciatorFrom: aString
- 
- 	| executiveClass winner priority |
- 	
- 	winner := 0.
- 	
- 	self instanciatorBase allSubclassesDo: [ :c | 
- 		priority := c canInstanciateFrom: aString.
- 		priority > winner ifTrue: [ 	winner := priority. 
- 									executiveClass := c ] ].
- 	
- 	^ executiveClass ifNil: [ self default ]!

Item was removed:
- ----- Method: FileExecutive>>dirClass (in category 'as yet unclassified') -----
- dirClass
- 
- 	^ Smalltalk at: #Directory ifAbsent: [ FileKernel ]!

Item was removed:
- ----- Method: FileKernel class>>newDirectoryFrom: (in category 'as yet unclassified') -----
- newDirectoryFrom: aPath
- 	                                                                                                            	
- 	^ self defaultExecutive current class newDirectoryFrom: aPath!

Item was removed:
- ----- Method: FileKernel>>isFileKernel (in category 'testing') -----
- isFileKernel
- 
- 	^true!

Item was removed:
- ----- Method: FileExecutive class>>default (in category 'as yet unclassified') -----
- default
- 
- 	^ FileLocalExecutive            !

Item was removed:
- ----- Method: FileLocalExecutive>>startAt:recursively:select:into: (in category 'executive actions') -----
- startAt: aDir recursively: beRecursive select: selectBlock into: results 
- 
- 	"Return a collection of rio's selected by passing
- 	the directoryEntry array to the selectBlock.
- 	
- 	The KernelRio implemetation of setStatFromEntryArray: 
- 	does not populate these rios with stat data.
- 	Rio's more verbose implementation does.
- 
- 	This can be called with startAt: aString, but if so beRecursive must be false.
- 		
- 	See primLookupEntryIn:index: for further details."
- 
- 	| index entryArray entry isDir fName |
- 
- 	index := 1.
- 
- 	[ (entryArray := self primLookupEntryIn: aDir asVmPathName index: index) notNil ] 
- 		whileTrue: [
- 			#badDirectoryPath = entryArray ifTrue: [
- 				^ results "(InvalidDirectoryError pathName: aDir value) signal" ].
- 
- 				isDir := entryArray at: 4.
- 				fName := entryArray at: 1.
- 				
- 				fName ~= '__MACOSX' ifTrue: [ 
- 					(entry := aDir / fName) 
- 									setStatFromDir: aDir andEntryArray:entryArray.
- 					
- 					isDir ifFalse: [  entry := entry asFile ].
- 				
- 					(selectBlock value: entry) ifTrue: [ results add: entry ].	
- 						
- 					(beRecursive and: [ isDir ]) 
- 						ifTrue: [ 
- 							self 
- 								startAt: entry
- 								recursively: beRecursive 
- 								select: selectBlock
- 								into: results   
- 						].	
- 				].
- 			index := index + 1
- 		].
- 	
- 	^ results!

Item was removed:
- ----- Method: FileLocalExecutive class>>current (in category 'accessing current') -----
- current
- 
- 	^ Test ifNil: [ Current ]
-  	
- !

Item was removed:
- ----- Method: FileKernel>>isFileKernelInstance (in category 'testing') -----
- isFileKernelInstance
- 
- 	^true!

Item was removed:
- ----- Method: String>>asDirectory (in category '*file-kernel') -----
- asDirectory
- 
- 	^ FileKernel newDirectoryFrom: self!

Item was removed:
- ----- Method: FileKernel class>>defaultExecutive (in category 'as yet unclassified') -----
- defaultExecutive
- 
- 	^ FileExecutive default!

Item was removed:
- ----- Method: FileExecutive class>>instanciatorBase (in category 'as yet unclassified') -----
- instanciatorBase
- 
- 	^ FileExecutive!

Item was removed:
- ----- Method: FileLocalExecutive class>>testEnd (in category 'image start up ') -----
- testEnd
- 
- 	Test := nil!

Item was removed:
- ----- Method: FileExecutive class>>newFileFrom: (in category 'as yet unclassified') -----
- newFileFrom: aString
- 
- 	^ (self instanciatorFrom: aString) makeNew: self fileClass from: aString
-     !

Item was removed:
- ----- Method: FileLocalExecutive class>>testFileSystem: (in category 'image start up ') -----
- testFileSystem: fs
- 
- 	^ Test := fs!



More information about the Packages mailing list