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

squeak-dev-noreply at lists.squeakfoundation.org squeak-dev-noreply at lists.squeakfoundation.org
Mon Nov 24 11:32:12 UTC 2008


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

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

Name: File-Base-kph.2
Author: kph
Time: 24 November 2008, 11:32:10 am
UUID: 48343982-132a-4a9b-80a0-f3ae3759f0e1
Ancestors: File-Base-kph.1

- support for using double dispatch to pick the write method for file transfers, local to remote, local to local, remote to local, or remote to remote.
- use OSProcess cp of CopyFilePlugIn is available
- ftp use OSProcess
- for bulk file moving, use multiple OSProcess invokations

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

Item was added:
+ ----- Method: File class>>tmp (in category 'as yet unclassified') -----
+ tmp
+ 
+ 	^ (Directory tmp / (SystemVersion current majorMinorVersion asString , '~', DateAndTime now asString)) asFile!

Item was changed:
+ ----- Method: FileFtpExecutive>>isDirectory: (in category 'basic') -----
- ----- Method: FileFtpExecutive>>isDirectory: (in category 'Rio-Grande') -----
  isDirectory: aRio
  
  	self ftpDo: [ :ftp | ftp changeDirectoryTo: home, aRio asVmPathName ] ifError: [ :ex | ^ false ].
  	 
  	^ true.!

Item was added:
+ ----- Method: File class>>tmpDo: (in category 'as yet unclassified') -----
+ tmpDo: aBlock
+ 
+ 	| tmpFile |
+ 	
+ 	[ tmpFile := self tmp.
+ 	  aBlock value: tmpFile ] ensure: [ tmpFile delete ]!

Item was changed:
+ ----- Method: FileFtpExecutive>>secondsForDay:month:yearOrTime:thisMonth:thisYear: (in category 'private') -----
- ----- Method: FileFtpExecutive>>secondsForDay:month:yearOrTime:thisMonth:thisYear: (in category 'as yet unclassified') -----
  secondsForDay: dayToken month: monthToken yearOrTime: ytToken 
  thisMonth: thisMonth thisYear: thisYear
  
  	| ftpDay ftpMonth pickAYear jDateToday trialJulianDate |
  
  	ftpDay := dayToken asNumber.
  	ftpMonth := Date indexOfMonth: monthToken.
  	(ytToken includes: $:) ifFalse: [
  		^(Date newDay: ftpDay month: ftpMonth year: ytToken asNumber) asSeconds
  	].
  	jDateToday := Date today dayOfYear.
  	trialJulianDate := (Date newDay: ftpDay month: ftpMonth year: thisYear) dayOfYear.
  	
  	"Date has no year if within six months (do we need to check the day, too?)"
  
  	"Well it appear to be pickier than that... it isn't just 6 months or 6 months and the day of the month, put perhaps the julian date AND the time as well. I don't know what the precise standard is, but this seems to produce better results"
  
  	pickAYear := (jDateToday - trialJulianDate) > 182 ifTrue: [
  		thisYear + 1	"his clock could be ahead of ours??"
  	] ifFalse: [
  		pickAYear := (trialJulianDate - jDateToday) > 182 ifTrue: [
  			thisYear - 1
  		] ifFalse: [
  			thisYear
  		].
  	].
  	^(Date newDay: ftpDay month: ftpMonth year: pickAYear) asSeconds +
  		(Time readFrom: (ReadStream on: ytToken)) asSeconds
  
  !

Item was added:
+ ----- Method: FileArchiveExecutive>>dir:add: (in category 'as yet unclassified') -----
+ dir: aDir add: aFileOrDir  
+ 
+ 	"I am an archive, add the file or create directory using aBaseDirectory 
+ 	 as the base reference."
+ 	
+ 	aFileOrDir isFile ifTrue: [ 	 
+ 		aDir archive addFile: aFileOrDir full asString as: aFileOrDir fileName.
+ 	].	
+ 	aFileOrDir isDirectory ifTrue: [ 
+ 		aDir archive addDirectory: aFileOrDir full asString as: aFileOrDir fileName.
+ 	]. 
+ 	!

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

Item was changed:
+ ----- Method: FileFtpExecutive>>deleteFile: (in category 'basic') -----
- ----- Method: FileFtpExecutive>>deleteFile: (in category 'Rio-Grande') -----
  deleteFile: aRio
  
  	self ftpDo: [ :ftp |
  		 
  		(self isFile: aRio) ifTrue: [ ftp deleteFileNamed: home , aRio asVmPathName ]
  		
  	].
  
  	aRio statIsNowInvalid.!

Item was added:
+ ----- Method: FileFtpExecutive>>dir:addFile: (in category 'external ftp') -----
+ dir: aDir addFile: aFile
+ 
+ 	^ aFile executive copyFile: aFile toRemoteFile: aDir / aFile fileName
+ 	
+ 	!

Item was changed:
+ ----- Method: FileFtpExecutive>>ftpDo: (in category 'ftp client') -----
- ----- Method: FileFtpExecutive>>ftpDo: (in category 'as yet unclassified') -----
  ftpDo: aBlock
   
  	| tmp result |
  
  	tmp := isKeepAlive.	
  	isKeepAlive := true.
  
  	[ result := aBlock value: self ftpClient. ] 
  
  		ensure: [  (isKeepAlive := tmp) ifFalse: [ client ifNotNil: [ client quit ] ] ].
  	
  	^ result!

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

Item was changed:
+ ----- Method: FileFtpExecutive>>ftpClient (in category 'ftp client') -----
- ----- Method: FileFtpExecutive>>ftpClient (in category 'as yet unclassified') -----
  ftpClient
  
  	client ifNotNil: [client isConnected ifTrue: [ ^ client ] ].
  
  	^ client := self ftpOpenClient!

Item was changed:
  ----- Method: File>>+ (in category 'public path') -----
  + ext
  
+ 	^ self newFrom: self value, ext asString!
- 	^ self newFrom: (self value, ext)!

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

Item was added:
+ ----- Method: FileFtpExecutive>>dir:add:fromBase: (in category 'basic') -----
+ dir: aDir add: aFileOrDir fromBase: aBaseDirectory
+ 	self ftpDo: [ :ftp | super dir: aDir add: aFileOrDir fromBase: aBaseDirectory ]  !

Item was added:
+ ----- Method: FileFtpExecutive>>copyLocalFile:toRemoteFile: (in category 'external ftp') -----
+ copyLocalFile: aFile toRemoteFile: bFile
+  
+ 	self class OSProcessOrNil ifNil: [ ^ aFile copyTo: bFile ].
+ 		
+  	self class OSProcessOrNil waitForCommand:
+ 	
+ 	'ftp -u "', url asString , bFile , '" "' , aFile asVmPathName	,'"' !

Item was changed:
+ ----- Method: FileFtpExecutive>>basicReader: (in category 'basic') -----
- ----- Method: FileFtpExecutive>>basicReader: (in category 'as yet unclassified') -----
  basicReader: aRio
  	
  	^ self ftpOpenForRead: aRio!

Item was changed:
+ ----- Method: FileFtpExecutive>>startAt:recursively:select:into: (in category 'basic') -----
- ----- Method: FileFtpExecutive>>startAt:recursively:select:into: (in category 'as yet unclassified') -----
  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 changed:
+ ----- Method: FileFtpExecutive>>ftpDo:ifError: (in category 'ftp client') -----
- ----- Method: FileFtpExecutive>>ftpDo:ifError: (in category 'as yet unclassified') -----
  ftpDo: aBlock ifError: errBlock
   
  	[ self ftpDo: aBlock. 
  	  ] on: TelnetProtocolError do: errBlock !

Item was changed:
+ ----- Method: FileFtpExecutive>>mkpath: (in category 'basic') -----
- ----- Method: FileFtpExecutive>>mkpath: (in category 'Rio-Grande') -----
  mkpath: aRio
  	self ftpDo: [ :ftp | super mkpath: aRio ]  !

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

Item was changed:
  ----- Method: Directory>>addAll: (in category 'directory/container actions') -----
+ addAll: someFD
- addAll: aCollectionOfFiles
  	
+ 	self addAll: someFD fromBase: nil!
- 	aCollectionOfFiles do: [ :each | self add: each ]!

Item was changed:
  ----- Method: Directory>>addAll:fromBase: (in category 'directory/container actions') -----
+ addAll: someFD fromBase: aDirectory
- addAll: aCollection fromBase: aDirectory
  
+ 	executive dir: self addAll: someFD fromBase: aDirectory!
- 	 aCollection do: [ :each | self add: each fromBase: aDirectory ]!

Item was added:
+ ----- Method: FileArchiveExecutive>>dir:add:fromBase: (in category 'as yet unclassified') -----
+ dir: aDir add: aFileOrDir fromBase: aBaseDirectory
+ 
+ 	"I am an archive, add the file or create directory using aBaseDirectory 
+ 	 as the base reference."
+ 
+ 	| localFileName |
+ 	
+ 	aDir validateIsContainer.
+ 	
+ 	localFileName := aFileOrDir linearRelativeTo: aBaseDirectory.		
+ 
+ 	aFileOrDir isFile ifTrue: [ 	 
+ 		aDir archive addFile: aFileOrDir value as: localFileName value.
+ 	].	
+ 	aFileOrDir isDirectory ifTrue: [ 
+ 		aDir archive addDirectory: aFileOrDir value as: localFileName value.
+ 	]. 
+ 	
+  !

Item was changed:
+ ----- Method: FileFtpExecutive>>ftpOpenClient (in category 'ftp client') -----
- ----- Method: FileFtpExecutive>>ftpOpenClient (in category 'as yet unclassified') -----
  ftpOpenClient
  
  	| loginSuccessful what client |
  	 
  	client := self FTPClient openOnHostNamed: self host.
  	loginSuccessful := false.
  	[loginSuccessful]
  		whileFalse: [
  			[loginSuccessful := true.
  			client loginUser: self user password: self password]
  				on: LoginFailedException
  				do: [:ex | 
  					what := UIManager default 
  						chooseFrom: #('enter password' 'give up') 
  						title: 'Would you like to try another password?'.
  					what = 1 ifFalse: [self error: 'Login failed.'. ^nil]
  							 ifTrue: [ self password: nil ].
  					loginSuccessful := false]].
   	
  	home := client pwd.
  	
  	^client!

Item was changed:
+ ----- Method: FileFtpExecutive>>fileSize: (in category 'basic') -----
- ----- Method: FileFtpExecutive>>fileSize: (in category 'Rio-Grande') -----
  fileSize: aRio
  
  	^ self ftpDo: [ :ftp | ftp getFileSize: home, aRio asVmPathName ]  !

Item was changed:
+ ----- Method: FileFtpExecutive>>delete: (in category 'basic') -----
- ----- Method: FileFtpExecutive>>delete: (in category 'Rio-Grande') -----
  delete: aRio
  	self ftpDo: [ :ftp | super delete: aRio ]  !

Item was added:
+ ----- Method: SharedQueue2>>setItems: (in category '*file-base') -----
+ setItems: anOrderedCollection
+ 	items := anOrderedCollection!

Item was added:
+ ----- Method: File>>parents (in category 'public modes') -----
+ parents
+ 	
+ 	| parent |
+  	
+ 	self value isEmpty ifTrue: [ ^ Array new ].
+ 	
+ 	self splitToPathAndName: [ :p :n |
+ 		parent := Directory new: p.
+  
+ 		(parent = self) ifTrue: [ ^ Array with: parent ].
+ 		 
+ 		^ parent parents copyWith: self
+ 	]
+ !

Item was added:
+ ----- Method: FileArchiveExecutive>>mkpath: (in category 'as yet unclassified') -----
+ mkpath: aDir	!

Item was changed:
+ ----- Method: FileFtpExecutive>>ftpParseEntry: (in category 'ftp client') -----
- ----- Method: FileFtpExecutive>>ftpParseEntry: (in category 'as yet unclassified') -----
  ftpParseEntry: ftpEntry
  	| permissions rs dateInSeconds thisYear thisMonth unkown user group size month day time filename |
  	thisYear := Date today year.
  	thisMonth := Date today monthIndex.
  
  	rs := ftpEntry readStream.
  	
  	permissions := rs upToSeparator.
  
  	permissions size < 10 ifTrue: [ ^ nil ].
  	
  	rs skipSeparators.
  	
  	unkown := rs upToSeparator.
  
  	rs skipSeparators.
  
  	user := rs upToSeparator.
  
  	rs skipSeparators.
  	
  	group := rs upToSeparator.
  
  	rs skipSeparators.
  
  	size := rs upToSeparator.
  
  	rs skipSeparators.
  
  	month := rs upToSeparator.
  
  	rs skipSeparators.
  
  	"Fix for case that group is blank (relies on month being 3 chars)" 
  	(size size = 3 and: [ size asNumber = 0 ]) ifTrue: [
  
  		month := size.
  		size := group.
  		group := 'blank'.
  
  	].
  
  	day := rs upToSeparator.
  
  	rs skipSeparators.
  	
  	time := rs upToSeparator.
  
  	rs skipSeparators.
  	
  	filename := rs upToEnd.
  		
  	dateInSeconds := self
  		secondsForDay: day 
  		month: month 
  		yearOrTime: time 
  		thisMonth: thisMonth 
  		thisYear: thisYear. 
  
  	^Array with: filename  "file name"
  			with: dateInSeconds "creation date"
  			with: dateInSeconds "modification time"
  			with: ( (permissions first) = $d or: [permissions first =$l]) "is-a-directory flag"
  			with: size asNumber  "file size"
  !

Item was changed:
+ ----- Method: FileFtpExecutive>>FTPClient (in category 'ftp client') -----
- ----- Method: FileFtpExecutive>>FTPClient (in category 'as yet unclassified') -----
  FTPClient
  
  	^ FTPClient"Debug"!

Item was changed:
+ ----- Method: FileFtpExecutive>>ftpKeepAliveDuring: (in category 'ftp client') -----
- ----- Method: FileFtpExecutive>>ftpKeepAliveDuring: (in category 'as yet unclassified') -----
  ftpKeepAliveDuring: aBlock
  
  	| tmp |
  
  	tmp := isKeepAlive.	
  	isKeepAlive := true.
  	aBlock ensure: [ isKeepAlive := tmp ]
  !

Item was changed:
+ ----- Method: FileFtpExecutive>>isFile: (in category 'basic') -----
+ isFile: aFile
- ----- Method: FileFtpExecutive>>isFile: (in category 'Rio-Grande') -----
- isFile: aRio
  
+ 	self ftpDo: [ :ftp | ftp getFileSize: home, aFile asVmPathName ] ifError: [ :ex | ^ false ].
- 	self ftpDo: [ :ftp | ftp getFileSize: home, aRio asVmPathName ] ifError: [ :ex | ^ false ].
  	 
  	^ true.!

Item was changed:
  FileKernel subclass: #File
  	instanceVariableNames: 'recursive rename adaptor binary'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'File-Base'!
  
+ !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 commentStamp: 'test 11/6/2008 00:05' prior: 0!
- Thinking out loud:
  
+ 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.
- Rio is an experimental version of ruby's rio in smalltalk, so as to compare with other approaches such as Fileman. Rio is implemented on RioKernel, rather than as a utility layer on top of FileDirectory, the intention being to do away with FileDirectory!!
- 
- I am wondering whether a lot of what happens in FileDirectory is absolutely necessary. So Rather than cover every eventuality, such as handling encodings of path strings (which is broken in most vms anyway) lets just try it without and see how far we get. We use tests to encapsulate what does work, and tests will highlight were we need an advance in architecture.  
- 
- For example for every basic example that I could think of '<example>' asVmPathString returns the same string as the original. Obviously it's not about basic examples.
- 
- So our use of a string-like class to store the path we are using should be agnostic to the implementation of string/encoding used. We can sort this out later if necessary in the interface to primitives.
- 
- In contrast to other approaches we define $/ as the standard delimieter for use within Squeak, translating for the underlying filesystem as needed. One reason for this being that Rio commonly uses $/ to assemble paths for readbility, and it doesnt really make sense to build $: delimited path with $/.
- 
- The #executive covers the interaction with the actual file system, and there is an executive for file systems with case insensitive filnames.
- 
- #rmdir does check for existence of the directory first (an improvement on legacy already!!)
- 
- #select: turns out to implement most of the guts of the fs Rio. It provides the basis for even the simpleset #stat and complex queries such as "files older than" via the stat record that is passed to the userBlock.
- 
- A beRecursive mode applies to all uses of #select:
- 
- By convention a mode change instanciates a fresh Rio instance. This treats existing instances as immutable. Mode changes are also intended to be temporary so that copying a new rio from this rio does not copy the recursive setting. (this may change).
- 
- A number of stats such as Rio>>#fileSize go via Rio>>#stat which searches for me in my parents directory!! This strikes me as a roundabout way of doing things. For multiple testing such as all the files newer than, #select: provides a much more efficient interface.
- 
- Stat results are cached, and the cache is shared by all Rios pointing to that file. The cache may be refreshed for all users via #restat, and may be invalidated via #statIsNoLongerValid  Given that a cached stat contains the fileName and the parent directory rio, this can be used to get quicker cached answers to #parent and #name without splitting the ipath every time. 
- 
- cwd is now available 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.
- 
- Pondering whether to have a quiet, error suppressing mode, but perhaps that is what error handlers are for.
- 
- 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 readUsing: [ :str |  ].
- aRio appendUsing: [ :str |  ].
- myRio := aRio delete write 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.
- 
- Rio is split into Rio and RioKernel, the latter being the minimal useful implementation for the KernelImage.
- 
- 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 ... ].
- 
- aStream copyTo: bStream has been implemented to be a reusable bit of code, since the same basic pattern seems to be used all over the place in slightly different forms. So now, Rio-#compress, is simply a Rio set to binary mode copied using the generic stream copy to a Rio set with a gzip adaptor.
- 
- I have moved Rio-compress to be implemented by the adaptor, this will allow different compression schemes to be supported. e.g. (Rio new: 'myFile.txt') gzip compress. Is handled by the GZip adaptor, there could be others.
- 
- So how to do 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 
- 
- Moving the above Directory interface into an adaptor RioAdaptorDir, enabled this to be pluggable with other back ends, i.e. Archives which use the same interface. RioAdaptorArchive is a subclass of RioAdaptorDir, and it handles both Zip and Tar archive (tar not yet supported).
- 
- Implemented and tested Win32 implementation, modelling Dos file Volumes as separate executives.
- Created a comprehensive platform independent test framework is needed to be able to verify all platform scenarious.
- 
- Lazy initialialization of executive or not? Changed to not, on the basis that it is easier to debug if exploring a rio if you can see what the executive actually is rather than a nil.
  
+ 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 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.
  
  !

Item was added:
+ ----- Method: Directory class>>mkTmpDir (in category 'as yet unclassified') -----
+ mkTmpDir
+ 
+ 	^ (self tmp / DateAndTime now asString) mkdir!

Item was changed:
  File subclass: #Directory
  	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'File-Base'!
  
+ !Directory commentStamp: 'kph 11/24/2008 01:59' prior: 0!
+ Could mode mkdir and mkpath into this adaptor.
+ 
+ TODO:
+ 
+ asFile to pick correct File subclass (like auto only better) auto can be retired!
- !Directory commentStamp: 'kph 4/12/2007 07:44' prior: 0!
- Could mode mkdir and mkpath into this adaptor.!

Item was changed:
+ ----- Method: FileFtpExecutive>>deleteDirectory: (in category 'basic') -----
- ----- Method: FileFtpExecutive>>deleteDirectory: (in category 'Rio-Grande') -----
  deleteDirectory: aRio
  
  	self ftpDo: [ :ftp | 
  		
  		ftp deleteDirectory: home, aRio asVmPathName.
  		
  	].
  
  	aRio statIsNowInvalid.!

Item was changed:
+ ----- Method: FileFtpExecutive>>ftpParseEntryOld: (in category 'ftp client') -----
- ----- Method: FileFtpExecutive>>ftpParseEntryOld: (in category 'as yet unclassified') -----
  ftpParseEntryOld: ftpEntry
  	| tokens longy dateInSeconds thisYear thisMonth |
  	thisYear := Date today year.
  	thisMonth := Date today monthIndex.
  	tokens := ftpEntry findTokens: ' '. 
  
  	tokens size = 8 ifTrue:
  		[((tokens at: 6) size ~= 3 and: [(tokens at: 5) size = 3]) ifTrue:
  			["Fix for case that group is blank (relies on month being 3 chars)"
  			tokens _ tokens copyReplaceFrom: 4 to: 3 with: {'blank'}]].
  	tokens size >= 9 ifFalse:[^nil].
  
  	((tokens at: 6) size ~= 3 and: [(tokens at: 5) size = 3]) ifTrue:
  		["Fix for case that group is blank (relies on month being 3 chars)"
  		tokens := tokens copyReplaceFrom: 4 to: 3 with: {'blank'}].
  
  	tokens size > 9 ifTrue:
  		[longy := tokens at: 9.
  		10 to: tokens size do: [:i | longy := longy , ' ' , (tokens at: i)].
  		tokens at: 9 put: longy].
  	dateInSeconds := self
  		secondsForDay: (tokens at: 7) 
  		month: (tokens at: 6) 
  		yearOrTime: (tokens at: 8) 
  		thisMonth: thisMonth 
  		thisYear: thisYear. 
  
  	^Array with: (tokens last)  "file name"
  			with: dateInSeconds "creation date"
  			with: dateInSeconds "modification time"
  			with: ( (tokens first first) = $d or: [tokens first first =$l]) "is-a-directory flag"
  			with: tokens fifth asNumber "file size"
  !

Item was changed:
+ ----- Method: FileFtpExecutive>>isKeepAlive (in category 'ftp client') -----
- ----- Method: FileFtpExecutive>>isKeepAlive (in category 'as yet unclassified') -----
  isKeepAlive
  
  	^ true!

Item was changed:
+ ----- Method: FileFtpExecutive>>mkdir: (in category 'basic') -----
+ mkdir: aDir
+ 	self ftpDo: [ :ftp | super mkdir: aDir ]  !
- ----- Method: FileFtpExecutive>>mkdir: (in category 'Rio-Grande') -----
- mkdir: aRio
- 	self ftpDo: [ :ftp | super mkdir: aRio ]  !

Item was added:
+ ----- Method: FileFtpExecutive>>copyRemoteFile:toLocalFile: (in category 'external ftp') -----
+ copyRemoteFile: aFile toLocalFile: bFile
+ 
+ 	self class OSProcessOrNil ifNil: [ ^ aFile copyTo: bFile ].
+ 		
+  	self class OSProcessOrNil waitForCommand:
+ 	
+ 	'ftp -o "', bFile asVmPathName, '" "' ,  url asString ,  aFile, '"'!

Item was added:
+ ----- Method: FileFtpExecutive>>copyRemoteFile:toRemoteFile: (in category 'external ftp') -----
+ copyRemoteFile: aFile toRemoteFile: bFile
+ 
+ 	^ aFile copyTo: bFile!

Item was changed:
  ----- Method: File>>split (in category 'public modes') -----
  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 = self) ifTrue: [ ^ Array with: self value ].
  		 
  		^ parent split copyWith: n
  	]
  
  !

Item was added:
+ ----- Method: FileFtpExecutive>>dir:addAll:fromBase: (in category 'basic') -----
+ dir: aDir addAll: someFD fromBase: 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 items done |
+ 	
+ 	self ftpDo: [ :ftp |
+ 	
+ 		self class OSProcessOrNil	ifNil: [^ super dir: aDir addAll: someFD fromBase: aBaseDir ].
+ 	
+ 		items := someFD collect: [ :aFileOrDir | (self dir: aDir mkpath: aFileOrDir fromBase: aBaseDir) -> aFileOrDir ].
+ 		items := items select: [ :ea | ea value isFile ].
+ 	].
+ 
+ 	queue := SharedQueue2 new setItems: items.
+ 	done := SharedQueue2 new.
+  	
+ 	self class prefFtpParallel timesRepeat: [
+ 			[
+ 				[ queue isEmpty ] whileFalse: [ 
+ 					queue nextOrNil ifNotNilDo: [ :ea | 
+ 						self dir: ea key addFile: ea value. 
+ 						done nextPut: 1
+ 					]
+ 				]
+ 			] fork.
+ 		].
+ 	
+ 	[ done size < items size ] whileTrue: [ Delay forMilliseconds: 100 ]. 
+  !

Item was changed:
+ ----- Method: FileFtpExecutive>>createDirectory: (in category 'basic') -----
- ----- Method: FileFtpExecutive>>createDirectory: (in category 'Rio-Grande') -----
  createDirectory: aRio
  
  	self ftpDo: [ :ftp | 
  		
  		ftp makeDirectory: home, aRio asVmPathName.
  		
  	].
  
  	aRio statIsNowInvalid.!

Item was added:
+ ----- Method: FileFtpExecutive class>>prefFtpParallel (in category 'as yet unclassified') -----
+ prefFtpParallel
+ 
+ 	"when ftp ing more than one file, maximum simultaneous transfers"
+ 	
+ 	^ 5!

Item was changed:
+ ----- Method: FileFtpExecutive>>basicWriter: (in category 'basic') -----
- ----- Method: FileFtpExecutive>>basicWriter: (in category 'as yet unclassified') -----
  basicWriter: aRio
  
  	^ self ftpOpenForWrite: aRio!

Item was changed:
+ ----- Method: FileFtpExecutive>>initialize (in category 'initialization') -----
- ----- Method: FileFtpExecutive>>initialize (in category 'as yet unclassified') -----
  initialize
  
  	isKeepAlive := false.!

Item was added:
+ ----- Method: FileRemoteExecutive>>toUrl: (in category 'as yet unclassified') -----
+ toUrl: aFD
+ 
+ 	^ url copy path: aFD full split allButFirst
+ !

Item was changed:
+ ----- Method: FileFtpExecutive>>user (in category 'ftp client') -----
- ----- Method: FileFtpExecutive>>user (in category 'as yet unclassified') -----
  user
  
  	^ url username ifNil: [ 'ftp' ]
  	!

Item was changed:
  ----- Method: Directory>>add: (in category 'directory/container actions') -----
+ add: aFD
+ 		 
+ 	^ self add: aFD fromBase: nil
- add: aFile 
- 	
- 	self validateIsDirectory.
- 	aFile validateIsFile.
- 	 
- 	^ aFile copyTo: self / aFile fileName
  	 !

Item was changed:
  ----- Method: Directory>>add:fromBase: (in category 'directory/container actions') -----
  add: aFileOrDir fromBase: aBaseDirectory
  
  	"I am a directory, add the file or create directory using aBaseDirectory 
  	 as the base reference."
  
- 	| newRio |
- 	
  	self validateIsDirectory.
  		
+ 	executive dir: self add: aFileOrDir fromBase: aBaseDirectory
+ 	 
- 	newRio := self / (aFileOrDir linearRelativeTo: aBaseDirectory).
  	
+  !
- 	aFileOrDir isFile ifTrue: [ 
- 		newRio parent ifAbsentDo: [ :newPath | newPath mkpath ].
- 		^ aFileOrDir copyTo: newRio 
- 	].
- 	
- 	aFileOrDir isDirectory ifTrue: [ ^ newRio mkpath ]. 
- 	
- !

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

Item was changed:
+ ----- Method: FileFtpExecutive>>ftpOpenForRead: (in category 'ftp client') -----
- ----- Method: FileFtpExecutive>>ftpOpenForRead: (in category 'as yet unclassified') -----
  ftpOpenForRead: aRio
  
  	self ftpClient openPassiveDataConnection.
  	self ftpClient sendCommand: 'RETR ', home , aRio asVmPathName.
  	
  	[client checkResponse]
  		on: TelnetProtocolError
  		do: [:ex |
  			client closeDataSocket.
  			ex pass].
  	
  	"we will wrap a socket for writing"
  	rw := #read.
  	
  	 ^ SocketStream on: self.!

Item was changed:
+ ----- Method: FileFtpExecutive>>rename:to: (in category 'basic') -----
- ----- Method: FileFtpExecutive>>rename:to: (in category 'Rio-Grande') -----
  rename: aRio to: bRio
  	
  	self ftpDo: [ :ftp | ftp renameFileNamed: home,  aRio asVmPathName to: home,  bRio asVmPathName ] 
  	ifError: [  
  		
  		aRio exists ifFalse:[ self error:'Attempt to rename a non-existent file or dir:' , aRio].
  	
  		bRio exists ifTrue:[ self error: 'Failed to rename, ', bRio,' already exists.' ].
  		
  	].
  	
  	aRio statIsNowInvalid. 
  	
  	
  	^ bRio
  
  !

Item was changed:
+ ----- Method: FileFtpExecutive>>ftpGetDirectory: (in category 'ftp client') -----
- ----- Method: FileFtpExecutive>>ftpGetDirectory: (in category 'Rio-Grande') -----
  ftpGetDirectory: dirString
  	"Return a stream with a listing of the current server directory.  (Later -- Use a proxy server if one has been registered.)"
  
  	| listing str ftpEntries |
  
  	self ftpDo: [ :ftp |
  		ftp changeDirectoryTo: dirString.
  		listing := ftp getDirectory ].	 
  		
  	str := ReadStream on: listing.
  	
  	(str respondsTo: #contentsOfEntireFile) ifFalse: [^ #()].
  	
  	ftpEntries := str contentsOfEntireFile findTokens: String crlf.
  		
  	^ ftpEntries 
  		collect:[:ftpEntry | self ftpParseEntry: ftpEntry ]
  		thenSelect: [:entry | entry notNil]!

Item was added:
+ ----- Method: FileFtpExecutive>>externalFtp:from:to: (in category 'external ftp') -----
+ externalFtp: getOrPut from: aFile to: bFile 
+  
+ 	File tmpDo: [ :cmds |
+ 
+ 		cmds writer: [ :str |
+ 			str <<  'open ' << self host; cr.
+ 			str <<  'user ' << self user << ' ' << self password; cr.
+ 			str <<  'binary' ; cr.
+ 			str <<  getOrPut  << ' "' << aFile << '" "' << bFile << '"' ; cr.
+ 			str <<  'quit' ; cr.
+ 		].
+ 
+ 		self class OSProcessOrNil waitForCommand: 'ftp -ig -s:' , cmds asVmPathName.
+  
+ 	].!

Item was changed:
+ ----- Method: FileFtpExecutive>>ftpOpenForWrite: (in category 'ftp client') -----
- ----- Method: FileFtpExecutive>>ftpOpenForWrite: (in category 'as yet unclassified') -----
  ftpOpenForWrite: aRio
  
  	self ftpClient openPassiveDataConnection.
  	self ftpClient sendCommand: 'STOR ', home , aRio asVmPathName.
  	
  	"we will wrap a socket for writing"
  	rw := #write.
  	
  	 ^ SocketStream on: self.!

Item was added:
+ ----- Method: FileFtpExecutive>>copyFile:toLocalFile: (in category 'external ftp') -----
+ copyFile: aFile toLocalFile: bFile
+ 
+ 	^ self copyRemoteFile: aFile toLocalFile: bFile!

Item was added:
+ ----- Method: FileFtpExecutive>>copyFile:toRemoteFile: (in category 'external ftp') -----
+ copyFile: aFile toRemoteFile: aDir
+ 
+ 	^ self copyRemoteFile: aFile toRemoteFile: aDir!

Item was changed:
  ----- Method: FileArchive>>add: (in category 'public') -----
+ add: aFD  
- add: aFile 
  	 
  	self validateIsContainer.
- 	aFile validateIsFile.
  	
+ 	executive dir: self add: aFD  !
- 	self archive addFile: aFile full asString as: aFile fileName.
- 	
- 	!

Item was changed:
  ----- Method: FileArchive>>add:fromBase: (in category 'public') -----
+ add: aFD fromBase: aBaseDirectory
- add: aFileOrDir fromBase: aBaseDirectory
  
  	"I am an archive, add the file or create directory using aBaseDirectory 
  	 as the base reference."
  
- 	| localFileName |
- 	
  	self validateIsContainer.
  	
+ 	executive dir: self add: aFD fromBase: aBaseDirectory!
- 	localFileName := aFileOrDir linearRelativeTo: aBaseDirectory.		
- 
- 	aFileOrDir isFile ifTrue: [ 	 
- 		self archive addFile: aFileOrDir value as: localFileName value.
- 	].	
- 	aFileOrDir isDirectory ifTrue: [ 
- 		self archive addDirectory: aFileOrDir value as: localFileName value.
- 	]. 
- 	
-  !

Item was changed:
+ ----- Method: FileFtpExecutive>>touch: (in category 'basic') -----
- ----- Method: FileFtpExecutive>>touch: (in category 'Rio-Grande') -----
  touch: aRio
  
  	self ftpDo: [ :dtp |
  	
  		ftp putFileStreamContents: (WriteStream with: String new) as: home , aRio asVmPathName
  	
  	]!

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

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

Item was removed:
- ----- Method: FileFtpExecutive>>rioClass (in category 'as yet unclassified') -----
- rioClass
- 
- 	^ File!

Item was removed:
- ----- Method: File class>>untrustedDirectory (in category 'as yet unclassified') -----
- untrustedDirectory
- 
-  	^ self new: (SecurityManager default primUntrustedUserDirectory)
- 	 !

Item was removed:
- ----- Method: FileArchive>>setRio: (in category 'accessing') -----
- setRio: aFile
- 
- 	super setRio: aFile.
- 	aFile executive: (FileArchiveExecutive file: aFile copy).
- 	aFile value: ''. "aFile executive root value."!

Item was removed:
- ----- Method: File class>>rioModesRenaming (in category 'documentation') -----
- rioModesRenaming
- "
- !!Renaming Mode:
- When in renaming mode changes to the Rio filename are reflected in the filesystem.
- 
- This allows rio to reuse all of its full featured filename accessors, for both renaming the Rio and also renaming files on disk.
- 
- As with all modes, there is a persistent and a temporary form.
- 
- persistent form:  #setModeToRenaming, sets the current rio to renaming.
- temporary form: #rename, yields a new rio in renaming mode.
- 
- "!

Item was removed:
- ----- Method: File class>>mkTmpDir (in category 'as yet unclassified') -----
- mkTmpDir
- 
- 	^ (self defaultExecutive getTempDirectory / DateAndTime now asString) mkdir!

Item was removed:
- ----- Method: File class>>examples (in category 'documentation') -----
- examples
- "
- (Rio new: '/usr/local') directories explore.
- 
- recursive mode can be used very naturally.
- 
- (Rio new: '/usr/local') all directories explore.
- 
- (Rio new: '/usr/local') all files explore.
- 
- (Rio new: '/usr/local') all select: [ :e | e modificationTime > ('1-1-05' asDate) ]. 
- 
- "!

Item was removed:
- ----- Method: File class>>rioStreams (in category 'documentation') -----
- rioStreams
- 
- "
- Using streams from a Rio
- 
- rio := Rio new: 'myFile.txt'.
- 
- contents := rio reader contents. - doesnt close the stream
- rio stream close.
- 
- " !

Item was removed:
- ----- Method: File class>>setToEnd (in category 'as yet unclassified') -----
- setToEnd!



More information about the Packages mailing list