[Pkg] Rio: File-Base-kph.18.mcz

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


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

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

Name: File-Base-kph.18
Author: kph
Time: 2 March 2009, 4:42:12 am
UUID: 7f381970-06e4-11de-a0af-000a95edb42a
Ancestors: File-Base-kph.17

+ Better instanciation code all round
+ handle line endings


=============== Diff against File-Base-kph.17 ===============

Item was added:
+ ----- Method: File class>>new: (in category 'as yet unclassified') -----
+ new: aPathOrFile
+  	
+ 	^ self localExecutive newOfClass: self from: aPathOrFile asString
+ 	!

Item was changed:
  ----- Method: File>>readStream (in category 'adaptor') -----
  readStream
  
  	| reader |
  
  	reader :=  self basicReader ifNil: [ ^ nil ].
  	
  	self isBinary 
  		ifTrue: [ reader binary ]
+ 		ifFalse: [ reader lineEndConvention: lineEndConvention ].
- 		ifFalse: [ reader wantsLineEndConversion: true ].
  		
  	
  	^ reader!

Item was changed:
  ----- Method: FileRemoteExecutive class>>makeNew:from: (in category 'as yet unclassified') -----
  makeNew: aClass from: aString
  
+ 	| exec path theUrl value |
- 	| exec path theUrl |
  
  	theUrl := aString asUrl.
  
  	path := String new writeStream.
  	
  	theUrl path do: [ :pathElem |
  		path nextPut: $/.
  		path nextPutAll: pathElem ].
  	
  	theUrl path: #().
  	
  	exec := self executiveForUrl: theUrl.
+ 	value := path contents.
+ 	
+ 	(value = '/' and: [ aClass ~= Directory ]) ifTrue: [ self error: 'not a file, please use asDirectory' ].
  
+ 	^ aClass executive: exec value: value.!
- 	^ aClass executive: exec value: path contents.!

Item was changed:
  ----- Method: Directory>>asFile (in category 'directory/container actions') -----
  asFile
  
+ 	^ self as: File!
- 	^ File newFrom: self!

Item was changed:
  ----- Method: File class>>thisVm (in category 'as yet unclassified') -----
  thisVm
  
+ ^ self new: (self localExecutive primVmPath)!
- ^ self new: (self defaultExecutive primVmPath)!

Item was added:
+ ----- Method: File>>lineEndConvention (in category 'public file') -----
+ lineEndConvention
+ 
+ 	^ lineEndConvention!

Item was added:
+ ----- Method: FileXML class>>validExtensions (in category 'as yet unclassified') -----
+ validExtensions
+ 
+ ^ #( 'xml' 'plist' 'xhtml' )!

Item was added:
+ ----- Method: File class>>validExtensions (in category 'documentation') -----
+ validExtensions
+ 
+ 	^ #()!

Item was changed:
  ----- Method: File>>gzip (in category 'public modes') -----
  gzip
  
+ 	^ self as: FileGzip!
- 	^ FileGzip newFrom: self!

Item was added:
+ ----- Method: FileFtpExecutive>>startAt:recursively:select:excluding:into: (in category 'basic') -----
+ startAt: rioOrString recursively: beRecursive select: selectBlock excluding: xList into: results 
+ 
+ 	"Return a collection of rio's selected by passing
+ 	the directoryEntry array to the selectBlock.
+ 	
+ 	This can be called with startAt: aString, but if so beRecursive must be false.
+ 		
+ 	See primLookupEntryIn:index: for further details."
+ 
+ 	| entry isDir fName |
+ 
+ 	(self ftpGetDirectory: home, rioOrString asVmPathName) keysAndValuesDo: [ :index :entryArray | 
+ 
+ 				fName := entryArray at: 1.
+ 	
+ 				(xList includes: fName) ifFalse: [ 
+ 
+ 					isDir := entryArray at: 4.
+ 
+ 					entry := ((isDir ifTrue: [ self class dirClass ] ifFalse: [ self class fileClass ]) 
+ 								executive: self value: rioOrString) 
+ 								pathJoin: fName; 
+ 								setStatFromDir: rioOrString 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   
+ 						]	
+ 				]
+  
+ 		].
+ 	
+ 	^ results!

Item was changed:
  ----- Method: FileGzip class>>validExtensions (in category 'as yet unclassified') -----
  validExtensions
  
+ ^ #( 'gz' 'gzip' )!
- ^ #( 'gz' )!

Item was added:
+ ----- Method: String>>asFile (in category '*file-base') -----
+ asFile
+ 
+ 	^ ((File classForPathWithExtension: self) ifNil: [ File ]) new: self!

Item was changed:
  ----- Method: Directory>>/ (in category 'directory/container actions') -----
  / morePath
  
+  	^ self copy pathJoin: morePath!
-  	^ self newFrom: (self pathJoin: morePath)!

Item was changed:
  ----- Method: Directory class>>untrusted (in category 'as yet unclassified') -----
  untrusted
  
+ 	^ self localExecutive untrustedDirectory   !
- 	^ self defaultExecutive untrustedDirectory   !

Item was added:
+ ----- Method: File class>>classForPathWithExtension: (in category 'documentation') -----
+ classForPathWithExtension: aPath
+ 
+ 	| ext |
+ 	ext := aPath copyAfterLast: $..
+ 	
+ 	self allSubclassesDo: [ :c | (c validExtensions includes: ext) ifTrue: [ ^ c ] ].
+ 		
+ 	^ nil
+  !

Item was changed:
  ----- Method: FileFtpExecutive>>copyUsing:from:to:relativeTo: (in category 'local/remote file copy') -----
  copyUsing: aSelector from: aDir to: someFD relativeTo: aBaseDir
  
  	"here we do two passes, first we ensure that all of the needed directories exist.
  	 for this we use our ususal ftp client.
  	
  	for the file transfers themselves we run n threads feeding from a shared queue
  	
  	"
  
  	| queue map done delay flg dest |
  	
+ 	flg := FileNotification isOverwrite.
- 	flg := FileNotification signal isOverwrite.
  
  	self ftpDo: [ :ftp |
- 	
  		map := self toDir: aDir mkpathAll: someFD relativeTo: aBaseDir.
  		
  		map := map select: [ :ea | 
  			dest := ea second.
  			dest isDirectory not and: [ flg or: [ dest exists not ] ]
  		]
  	].
  
  	delay := Delay forMilliseconds: 100.
  	queue := SharedQueue2 new setItems: map copy.
  	done :=  SharedQueue2 new.
  	
   	
  	self class prefFtpParallel timesRepeat: [
  			[
  				[ queue isEmpty ] whileFalse: [ 
  					queue nextOrNil ifNotNilDo: [ :ea | 
  						[ self perform: aSelector withArguments: ea ] ensure: [ done nextPut: ea ].
  					]
  				]
  			] fork.
  		].
  	
  	[ done size < map size ] whileTrue: [ delay wait ]. 
   
  	^ map collect: [ :ea | ea second ]!

Item was added:
+ ----- Method: File class>>documentationExtensions (in category 'documentation') -----
+ documentationExtensions
+ "
+ StandardFileStream-#retryWithGC: execBlock until: testBlock forFileNamed: fullName
+ 
+ trivial change allows fullName to be passed in as a rio, since the rio handles the equivalent of String-sameAs:. However
+ rio's implementation of sameAs: can be adjusted according to the platform.
+ _
+ Object-#isFileOrDirectory for testing
+ _
+ String-#asFile for conveniance
+ String-#asDirectory for conveniance
+ 
+ _
+ FileStream close now returns the file i.e. the File instance that opened it.
+ Stream use: [ :str | ]  now includes an ensure close block, 
+ and returns the return value of that close.
+ _
+ FileDirectory-#fullNameFor: 
+ adding asString allows a Rio to be passed in to many FileDirectory functions.
+ 
+ "!

Item was added:
+ ----- Method: FileArchiveExecutive>>startAt:recursively:select:excluding:into: (in category 'as yet unclassified') -----
+ startAt: rioOrString recursively: beRecursive select: selectBlock excluding: xList into: results 
+ 
+ 	"this unpleasent method repackages the flat archive as a hierarchical structure that
+ 	can be recursively traversed like a normal directory."
+ 	
+ 	| membersBelow subDirs dir |
+ 	
+  	membersBelow := archive members.
+ 	
+  	rioOrString isEmpty
+ 		ifTrue: [ 
+ 			dir := ''.
+ 			]
+ 		ifFalse: [ 
+ 			dir := rioOrString value.
+ 			dir last ~= $/ ifTrue: [ dir := dir , '/' ].
+  			membersBelow := membersBelow select: [ :member | 
+ 				(member fileName ~= dir) and: [member fileName beginsWith: dir]
+ 			].
+ 	].
+ 
+ 	subDirs := (membersBelow reject: [:member | xList includes: member fileName ])
+ 	
+ 		select: [ :member | 
+ 			| pathBelow entry |
+ 			pathBelow := member fileName allButFirst: dir size. 
+ 			pathBelow last = $/ ifTrue: [ pathBelow := pathBelow allButLast ].
+ 			(pathBelow includes: $/) 
+ 				ifFalse: [
+ 					
+ 					entry := member isDirectory 
+ 						ifTrue: [ self class dirClass executive: self value: member fileName ]
+ 						ifFalse: [ self class fileClass executive: self value: member fileName ].
+ 				
+ 					entry setStatFromDir: rioOrString andEntryArray: 
+ 						(Array 
+ 							with: pathBelow
+ 							with: "member lastModTime" 0
+ 							with: "member lastModTime" 0 
+ 							with: member isDirectory).
+ 					(selectBlock value: entry) ifTrue: [ results add: entry ].
+ 					false 
+ 				] 
+ 				ifTrue: [ true ].
+ 		].
+ 
+ 	beRecursive ifTrue: [
+ 		subDirs do: [ :aDir |
+ 			self startAt: aDir fileName recursively: beRecursive select: selectBlock excluding: xList into: results 
+ 		].
+ 	]. 	 
+ 	
+ 	^ results!

Item was changed:
  ----- Method: File class>>/ (in category 'as yet unclassified') -----
+ / aPathable
- / a
  
+ 	"we are the local cwd"
+ 	^ self localExecutive in: [:exec |
+ 			exec dirClass executive: exec value: aPathable asString
+ 	  ]
- 	^ Directory new: a
  !

Item was added:
+ ----- Method: Directory class>>new (in category 'as yet unclassified') -----
+ new
+ 
+ 	^ Directory fromString: ''!

Item was changed:
  FileKernel subclass: #File
  	instanceVariableNames: 'recursive rename adaptor binary'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'File-Base'!
  
+ !File commentStamp: 'test 3/1/2009 04:03' prior: 0!
+ (see also #documentationExtensions)
+ 
+ Features Overview
+ 
+ File/Directory was inspired by ruby's rio which enables local, remote, and archived file systems to be used transparently. To achieve this a generic stream copy function has been developed (aStream copyTo: bStream) and we are able to expose the working stream of FtpClient so you can stream directly to a remote file. We also support transparent streaming to compressed files (gzip) and (plan to) support file archives (zip) as if they were a filesystem. Transparent streaming to a remote compressed file is still available as a exercise for the reader to implement ;)
- !File commentStamp: 'kph 11/24/2008 11:28' prior: 0!
- File/Directory was inspired by ruby's rio which enables local and remote files to be used transparently. To achieve this a generic stream copy function has been developed (aStream copyTo: bStream) and we are able to expose the working stream of FtpClient so you can stream directly to a remote file. We also support file archives (zip) as if they were a filesystem, and transparent streaming to compressed files (gzip). [transparent streaming to a remote compressed file is still available as a exercise for the reader to implement ;) ]
  
  File/Directory is a standalone package, it does not use any of the existing FileDirectory classes. It is separated into File-Kernel and File-Base, where the former provides a minimal working subset for KernelImages to access local filesystems.
  
  Local file copying is handled by the fileCopyPlugin if it is present, if not OSProcess 'cp' is used, and as a last resort a full stream to stream copyTo: is performed (but this does update modification time).
  
+ Remote file upload or download is handled by OSProcess 'ftp' if it is present. Multiple file transfers (#addAll: #addTree:) are invoked N at a time (where N is initially 5). Copying from a remote file to another remote file is handled by the internal stream copy function between two internal FTPClients.
+ 
+ Instanciation:
+ 
+ The main instanciation is via: File new: 'file. Directory new: 'dir'. FileXML new: 'blah.xml' etc. (where new: calls fromString:)
+ Conversion between file types/mode subclasses is avaiable via: #as: e.g. (File new:'file.xml') as: FileXML. (e.g. #xml #gzip)
+ 
+ 'file' asFile. 'aDirectory asDirectory. - are provided as readable, intelligent, convenience methods.
+ #asFile attempts to interpet any fileExtension according to those registered in #validExtensions.
+ 
+ All operations including instanciation are performed by an executive, the local file system executive is available via #localExecutive. "Pretending" is supported, in the event that you wish File/Directory to pretend to be on another file system.
+ (FileLocalDosExecutive executiveForVolume: 'G:\') pretendDuring: [ FileKernel localExecutive ] --> FileLocalDosExecutive(G:\)
+ Pretending uses Notifications, when it is enabled, but not otherwise, so in normal use there is no speed penalty for local executive look up.
+ 
+ Files are told of the local line ending convention on instanciation. You can override this when you set the ascci mode asciiCr/asciiCrLf/asciiLf
+ 
+ 
+ 
- Remote file upload or download is handled by OSProcess 'ftp' if it is present. Multiple file transfers are invoked N at a time (where N is initially 5). Copying from a remote file to another remote file is handled by the internal stream copy function.
  Caveats: No explicit support has been coded for alternative character encodings for paths. File paths are stored as Strings and sent to primitives via asVmPathname.
  
  Known Issues (features): A File/Directory instance on windows, when moved to a unix machine will refer to the file with that path name (with \s) in the local directory. This allows a unix machine to provide an alias to the correct location. (thats the theory anyway)
  
  We define $/ as the standard delimieter for use within Squeak, translating for the underlying filesystem as needed.  
  
  The #executive covers the interaction with the actual file system, and there is an executive for file systems with case insensitive filenames.
  
  #rmdir does check for existence of the directory first (an improvement on legacy already!!)
  
  #select: Provides the core of the implementation. It provides the basis for even the simpleset #stat or complex queries such as "files older than", and it has a recursive mode (#all) which applies to all uses of #select:
  
  Mode changes instanciate a fresh instance, existing instances are effectively immutable. 
  
  Stat results are cached, and the cache is shared by all references pointing to that file.
  
  ilable as a Class, enabling the readable form: Cwd / 'hello.txt' in code
  
  Cool Null support for the following has been removed.
  myFile := myFileRio ifFile reading.
  newRio := myFileRio ifFile renameTo: 'newname'.
  
  Rather than have #renameTo:overwriting: the following does the same job just as concisely.
  oldRio renameTo: (newRio delete).
  oldRio renameTo: (newRio forceNewFile).  is equivalent also.
  
  Ruby Rio has the ability to tell the rio what the expected extension is, which it then takes into account when calculating the #basename then takes into account. So there is an #ext and an #extname, which gets kind of confusing. So if we simply define basename as the #fileName upto the last $., and the ext as the rest that should be enough.
  
  Implementing #delete.
  '\' asRio deleteTree may not be a good idea!! Do we need a guard. Ok, lets set it so that #delete wil do the job of deleteTree if the recursive flag is set.
  usage: aRio all rmdir - makes sense
  usage: aRio rmdir - makes sense if dir is empty.
  
  Function of 'force'NewFileNamed: is now handled by
  fileStream := aRio delete writer.
  fileStream := aRio forceNewFile writer.
  
  And the block case, instead of implementing three methods.
  aRio reader: [ :str |  ].
  aRio appender: [ :str |  ].
  myRio := aRio delete writer use: [ :str | str, 'hello'; cr ].
  
  we use #use: which unlike #in: ensures the stream is closed for us
  aRio writer use: [ :str |  ].
  aRio writer use: [ :str |  ].
  
  FileStream #close to return the stream's rio (none of the existing senders of #close use the return value)
  this allows continuing with the rio after the cascade, or using the result in assigment.
  (myRio writer << 'a bit' << 'abit more') close isFile ifTrue: [ 'it s a file' ]
  myRio := ('test' asRio writer << 'a bit' << 'a bit more') close.
  myRio := 'test' asRio writer: [ :w | w,'hello';cr ].
  myRio read contents.
  
  Defined #reader: and #writer: to take a block.
  instead of aRio reader use: [ :str | ], you can write aRio reader: [ :inStream | ... ].
  instead of aRio writer use: [ :str | ], you can write aRio writer: [ :outStream | ... ].
  #appender: is also available and is equivalent to writer: [ :out | out setToAppend. out ... ].
  
  Copying multiple files to a directory or archive:
  aDirectory copyTo: bDirectory. Could be done as aDirectory entries copyTo: bDirectory, but we havent got any methods on OrderedCollection to do that with, so it would have to be. bDirectory copyFrom: aDirectory all entries. That doesnt read correctly and it looks like you might be overwriting bDirectory. I think that "bDirectory addAll: aDirectory all entries" is fairly unambiguous. aFile copyTo: bDirectory makes sense but rather than overload #copyTo: with multiple behavours , lets keep it file to file only, and use bDirectory add: aFile as an equally unambigous version. To be useful when adding a tree of directory and files we need to know the base directory we are starting from, and all of the files as relative paths to that pase directory. The implementation of simpleRelativeTo: is brilliantly simple especially compared to the methods used in Archive-addTree: etc. 
  
  The result is a quite simple and versatile, 
  1. aDirectory add: aFile , 
  2. aDirectory addAll: acollection
     - e.g. aDirectory addAll: (myOutput all filesMatching: #('*.image' '*.changes') ).
  3. aDirectory addTree: aDirectory (and all of its contents). 
  4. The generic version of addTree: which can be used with a hand crafted collection of files,
     missing directories are created.
  	aDirectory addAll: aCollection fromBase: aDirectory 
  
  RioFtpFileSystem executive depends upon MCPasswordManager to look after passwords.
  
+ Note: #select:/#entries/filesMatching: etc do not walk '__MACOSX' or '.DS_Store', but 'test' all delete does.!
- !

Item was changed:
  ----- Method: File>>rmdir (in category 'public dir') -----
  rmdir
  	"as a minor saftey precaution, the directory must be empty or we
  	 must be explicitly set in recursive mode (rmdir resets recursive mode).
  	"
  	self isDirectory ifFalse: [ ^self ].
  	
  	self isRecursive 
  		ifTrue: [ recursive := false.
+ 				 (executive in: self excluding: #() select: [:d | true ])
+ 					do: [ :ea | ea beRecursive delete ].
+ 				 recursive := true ].
- 				 self entries do:  [:d | d beRecursive delete ] ].
  
  	executive deleteDirectory: self
  	!

Item was added:
+ ----- Method: File>>asciiLf (in category 'public modes') -----
+ asciiLf
+ 
+ 	binary := false.
+ 	lineEndConvention := #lf.!

Item was added:
+ ----- Method: File class>>new (in category 'as yet unclassified') -----
+ new
+ 
+ 	^ self error: 'File new - is invalid use Directory new'!

Item was changed:
  ----- Method: File>>xml (in category 'public modes') -----
  xml
  
+ 	^ self as: FileXML!
- 	^ FileXML newFrom: self!

Item was added:
+ ----- Method: FileFtpExecutive>>in:excluding:select: (in category 'basic') -----
+ in: aRio excluding: xList select: selectBlock
+ 
+ 	^ self ftpDo: [ :c | super in: aRio excluding: xList select: selectBlock ]!

Item was changed:
  ----- Method: File>>asDirectory (in category 'public modes') -----
  asDirectory
  
+ 	^ self as: Directory!
- 	^ Directory newFrom: self!

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

Item was changed:
  ----- Method: File>>contents: (in category 'public file') -----
  contents: aStreamAble
  
   	"aStreamable refers to implementers of << and hence putOn: 
   	And so would write out an array of strings"
   
+  	^ self asFile writer: [ :out | out << aStreamAble ].!
-  	self writer: [ :out | out << aStreamAble ].!

Item was changed:
  ----- Method: Directory class>>root (in category 'as yet unclassified') -----
  root
  
+ 	^ self localExecutive root!
- 	^ self defaultExecutive current root!

Item was added:
+ ----- Method: File>>asciiCr (in category 'public modes') -----
+ asciiCr
+ 
+ 	binary := false.
+ 	lineEndConvention := #cr.!

Item was added:
+ ----- Method: String>>asDirectory (in category '*file-base') -----
+ asDirectory
+ 
+ 	^ Directory new: self!

Item was added:
+ ----- Method: File>>asciiCrLf (in category 'public modes') -----
+ asciiCrLf
+ 
+ 	binary := false.
+ 	lineEndConvention := #crlf.!

Item was changed:
  ----- Method: File>>from: (in category 'copying instanciation') -----
  from: pathOrRio
  		
+ 	pathOrRio isEmpty ifTrue: [ value := ''].
- 	(pathOrRio isEmpty and: [ self class name ~= #Cwd ]) ifTrue: [ value := ''].
  	
  	(pathOrRio isKindOf: FileKernel) ifTrue: [ 
  			self setStat: pathOrRio getStat.
  			pathOrRio isBinary ifTrue: [ self beBinary ].
  	].
  
  	^ self value: pathOrRio!

Item was changed:
  ----- Method: Directory class>>tmp (in category 'as yet unclassified') -----
  tmp
  
+ 	^ self localExecutive getTempDirectory   !
- 	^ self defaultExecutive current getTempDirectory   !

Item was added:
+ ----- Method: Directory class>>cwd (in category 'as yet unclassified') -----
+ cwd
+ 
+ 	^ Directory fromString: ''!

Item was removed:
- ----- Method: File class>>instantiation (in category 'documentation') -----
- instantiation
- "
- Rio has an instanciation scheme which provides many dimensions for specialisation, dividing 
- responsibilities logically among the components involved.
- 
- A path string can specify a specialised protocol which refers to a particular domain 
- e.g. ftp remote host. The domain executive may in turn choose which class to represent
- the elements which it manages. The elements perform all primitive manipulations 
- via the domain executive.
- 
- Typical Instanciation Route:
- 
- <aPathString> asRio. - gives an instance of Rio, via Rio new: aPathOrARio
- 
- Rio #new: traverses its subclasses asking if any #canInstanciate: so as to allow 
- specific subclasses to handle protocols, or any other encoded-in-path-string specialisations.
- As a fallback Rio handles the default case.
- 
- The elected class, is sent #new in order to create an empty instance, which will be populated #from: <aPathString> 
- 
- The default behaviour of #new is to ask the #defaultExecutive, 'LocalFileSystemCurrent' to instanciate an instance that implements the appropriate behaviour for that domain via: #makeNewRioOfClass: <theClass>, the default be being <theClass>-#basicNew.
- "!

Item was removed:
- ----- Method: File>>linearRelativeTo: (in category 'public dir') -----
- linearRelativeTo: aDirectoryOrFile
-  	| tmp |
- 	self full = aDirectoryOrFile full ifTrue: [ ^ Directory new: '' ].
- 
- 	tmp := (self parent linearRelativeTo: aDirectoryOrFile) / self fileName.	
- 	
- 	^tmp
- 	 !

Item was removed:
- ----- Method: File>>asUrl (in category 'public modes') -----
- asUrl
- 
- 	^ executive toUrl: self!

Item was removed:
- ----- Method: FileFtpExecutive>>in:select: (in category 'basic') -----
- in: aRio select: selectBlock
- 
- 	^ self ftpDo: [ :c | super in: aRio select: selectBlock ]!

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

Item was removed:
- ----- Method: Cwd>>printOn: (in category 'as yet unclassified') -----
- printOn: str
- 
- 	str , '(', self class name, ' new)'
- 	
- !

Item was removed:
- ----- Method: FileFtpExecutive>>startAt:recursively:select:into: (in category 'basic') -----
- startAt: rioOrString recursively: beRecursive select: selectBlock into: results 
- 
- 	"Return a collection of rio's selected by passing
- 	the directoryEntry array to the selectBlock.
- 	
- 	This can be called with startAt: aString, but if so beRecursive must be false.
- 		
- 	See primLookupEntryIn:index: for further details."
- 
- 	| entry isDir |
- 
- 	(self ftpGetDirectory: home, rioOrString asVmPathName) keysAndValuesDo: [ :index :entryArray | 
- 	
- 				(entry := rioOrString / (entryArray at: 1)) 
- 									setStatFromDir: rioOrString andEntryArray:entryArray.
- 
- 				isDir := entryArray at: 4.
- 
- 				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   
- 					].	
-  
- 		].
- 	
- 	^ results!

Item was removed:
- Directory subclass: #Cwd
- 	instanceVariableNames: ''
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'File-Base'!

Item was removed:
- ----- Method: Cwd>>newFrom: (in category 'as yet unclassified') -----
- newFrom: pathOrFile
- 
- 	^ File executive: executive value: pathOrFile!

Item was removed:
- ----- Method: FileArchiveExecutive>>startAt:recursively:select:into: (in category 'as yet unclassified') -----
- startAt: rioOrString recursively: beRecursive select: selectBlock into: results 
- 
- 	"this unpleasent method repackages the flat archive as a hierarchical structure that
- 	can be recursively traversed like a normal directory."
- 	
- 	| membersBelow subDirs dir |
- 	
-  	membersBelow := archive members.
- 	
-  	rioOrString isEmpty
- 		ifTrue: [ 
- 			dir := ''.
- 			]
- 		ifFalse: [ 
- 			dir := rioOrString value.
- 			dir last ~= $/ ifTrue: [ dir := dir , '/' ].
-  			membersBelow := membersBelow select: [ :member | 
- 				(member fileName ~= dir) and: [member fileName beginsWith: dir]
- 			].
- 	].
- 
- 	subDirs := membersBelow select: [ :member | 
- 		| pathBelow entry |
- 		pathBelow := member fileName allButFirst: dir size. 
- 		pathBelow last = $/ ifTrue: [ pathBelow := pathBelow allButLast ].
- 		(pathBelow includes: $/) 
- 			ifFalse: [
- 				
- 				
- 				entry := member isDirectory 
- 					ifTrue: [ self class dirClass executive: self value: member fileName ]
- 					ifFalse: [ self class fileClass executive: self value: member fileName ].
- 				
- 				entry setStatFromDir: rioOrString andEntryArray: 
- 					(Array 
- 						with: pathBelow
- 						with: "member lastModTime" 0
- 						with: "member lastModTime" 0 
- 						with: member isDirectory).
- 				(selectBlock value: entry) ifTrue: [ results add: entry ].
- 				false 
- 			] 
- 			ifTrue: [ true ].
- 	].
- 
- 	beRecursive ifTrue: [
- 		subDirs do: [ :aDir |
- 			self startAt: aDir fileName recursively: beRecursive select: selectBlock into: results 
- 		].
- 	]. 	 
- 	
- 	^ results!

Item was removed:
- ----- Method: Cwd>>split (in category 'as yet unclassified') -----
- split
- 
- ^ Array new!

Item was removed:
- ----- Method: File>>os (in category 'public modes') -----
- os
- 
- 	^ RioOSProcess new: self!

Item was removed:
- ----- Method: File>>asMatchedList (in category 'enumeration') -----
- asMatchedList
- 
- 	^ self parent filesMatching: self fileName!

Item was removed:
- ----- Method: File class>>extensions (in category 'documentation') -----
- extensions
- "
- StandardFileStream-#retryWithGC: execBlock until: testBlock forFileNamed: fullName
- 
- trivial change allows fullName to be passed in as a rio, since the rio handles the equivalent of String-sameAs:. However
- rio's implementation of sameAs: can be adjusted according to the platform.
- _
- Object-#isRio for testing
- _
- String-#asRio for coercion
- _
- FileStream close now returns the file i.e. the Rio that opened it.
- Stream in: [ :str | ]  now includes an ensure close block, 
- and returns the return value of that close.
- _
- FileDirectory-#fullNameFor: 
- 
- adding asString allows a Rio to be passed in to many FileDirectory functions.
- 
- "!

Item was removed:
- ----- Method: Cwd class>>new: (in category 'public instanciation') -----
- new: pathOrFile
- 
- 	^ Directory new: pathOrFile!

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



More information about the Packages mailing list