[Pkg] Rio: Rio-Grande-kph.39.mcz

squeak-dev-noreply at lists.squeakfoundation.org squeak-dev-noreply at lists.squeakfoundation.org
Fri Nov 7 02:58:42 UTC 2008


A new version of Rio-Grande was added to project Rio:
http://www.squeaksource.com/Rio/Rio-Grande-kph.39.mcz

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

Name: Rio-Grande-kph.39
Author: kph
Time: 7 November 2008, 2:58:07 am
UUID: 22b148f9-a534-434d-b225-c2078168aad7
Ancestors: Rio-Grande-kph.38

ftp support complete(?)

=============== Diff against Rio-Grande-kph.38 ===============

Item was changed:
  ----- Method: Rio>>contents (in category 'public file') -----
  contents 
   
+   self reader: [ :str | ^ str upToEnd ].
-   self reader: [ :str | ^ str contents ].
  
  	^ nil!

Item was added:
+ ----- Method: RioFtpFileSystem>>isDirectory: (in category 'as yet unclassified') -----
+ isDirectory: aRio
+ 
+ 	self ftpDo: [ :client | client changeDirectoryTo: home, aRio asVmPathName ] ifError: [ :ex | ^ false ].
+ 	 
+ 	^ true.!

Item was added:
+ ----- Method: RioFtpFileSystem>>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: RioFtpFileSystem>>receiveDataSignallingTimeout:into:startingAt: (in category 'wrap socket') -----
+ receiveDataSignallingTimeout: timeout
+ 					into: inBuffer startingAt: inNextToWrite
+ 
+ 	^ ftpClient dataSocket receiveDataSignallingTimeout: timeout
+ 					into: inBuffer startingAt: inNextToWrite!

Item was changed:
  ----- Method: Rio>>mTime (in category 'accessing stat') -----
  mTime
  
+ 	^ self stat mTime!
- ^self stat mTime!

Item was added:
+ ----- Method: RioFtpFileSystem>>rootString (in category 'as yet unclassified') -----
+ rootString
+ 
+ 	^ '/'!

Item was added:
+ ----- Method: RioFtpFileSystem>>deleteFile: (in category 'as yet unclassified') -----
+ deleteFile: aRio
+ 
+ 	self ftpDo: [ :client |
+ 		 
+ 		(self isFile: aRio) ifTrue: [ client deleteFileNamed: home , aRio asVmPathName ]
+ 		
+ 	].
+ 
+ 	aRio statIsNowInvalid.!

Item was added:
+ ----- Method: RioFtpFileSystem>>isOtherEndClosed (in category 'wrap socket') -----
+ isOtherEndClosed
+ 
+ 	^ (ftpClient dataSocket ifNil: [ ^ true ]) isOtherEndClosed!

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

Item was added:
+ ----- Method: RioFtpFileSystem>>password (in category 'as yet unclassified') -----
+ password
+ 
+ 	^ url password ifNil: [ (self MCPasswordManager default queryPasswordAt: url asString user: (self user ifNil:[^'squeak']))  ]
+ 	
+ 
+  !

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

Item was changed:
  ----- Method: Rio>>mkdir (in category 'public dir') -----
  mkdir
+ 
+ 	"to avoid failing if already present, use:
-   	"to avoid failing if already present use
  	myFileRio ifAbsent mkdir"
+ 	 
+ 	executive mkdir: self!
- 	
- 	self isDirectory ifTrue: [ ^ self error: 'directory already exists' ].
- 	executive createDirectory: self  !

Item was changed:
  ----- Method: Rio>>writer (in category 'public file') -----
  writer
  	
+ 	^ self adaptor writeStream!
- 	^ self writeStream!

Item was added:
+ ----- Method: FTPClient>>getFileSize: (in category '*rio-grande') -----
+ getFileSize: fileName
+ 	self sendCommand: 'SIZE ' , fileName.
+ 	self checkResponse.
+ !

Item was changed:
  ----- Method: Rio>>delete (in category 'public file') -----
  delete 
  
+ 	executive delete: self!
- 	self isDirectory ifTrue: [ ^ self rmdir ].
- 	
- 	"Delete the file of the given name if it exists.
- 	
- 	the if present functionality can be obtained via
- 	myFileRio ifFile delete.
- 		
- 	"
- 	 
- 	executive deleteFile: self.!

Item was added:
+ ----- Method: PositionableStream>>copyTo:size:withProgress: (in category '*rio-grande') -----
+ copyTo: out size: aSize withProgress: label 
+ 
+ 	| buffer barPos read first |
+  	
+ 	self atEnd ifTrue: [ ^ self ].
+ 	
+ 	first := self next.
+ 	
+ 	buffer := (first isCharacter 
+ 				ifTrue: [ String ] 
+ 				ifFalse: [ out binary. ByteArray ]) new: 50000.
+ 	
+ 	out nextPut: first.
+ 
+ 	label asString displayProgressAt: Sensor cursorPoint
+ 		from: (barPos := 0) to: (self size)
+ 		during: [:bar |
+ 				[ self atEnd ] whileFalse: [
+ 				bar value: barPos.
+ 				out nextPutAll: (read := self nextInto: buffer).
+ 				barPos := barPos + read size ].
+ 		].!

Item was changed:
  ----- Method: Rio>>touch (in category 'public file') -----
  touch
  
+ 	executive touch: self!
- 	self writer close!

Item was added:
+ ----- Method: RioFtpFileSystem>>sendData:count: (in category 'wrap socket') -----
+ sendData: outBuffer count: n
+ 
+ 	ftpClient dataSocket sendData: outBuffer count: n!

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

Item was added:
+ ----- Method: RioFtpFileSystem>>closeAndDestroy: (in category 'wrap socket') -----
+ closeAndDestroy: timeout
+ 
+ 	ftpClient closeDataSocket.
+ 	ftpClient checkResponse.
+ 	
+ 	rw = #write ifTrue: [ ftpClient checkResponse ].!

Item was changed:
  ----- Method: RioFtpFileSystem>>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."
  
  	| entryRio |
  
+ 	(self ftpGetDirectory: home, rioOrString asVmPathName) keysAndValuesDo: [ :index :entryArray | 
- 	(self ftpGetDirectory: rioOrString asVmPathName) keysAndValuesDo: [ :index :entryArray | 
  	
  				(entryRio := rioOrString / (entryArray at: 1)) 
  									setStatFromDir: rioOrString andEntryArray:entryArray.
  
  				(selectBlock value: entryRio) ifTrue: [ results add: entryRio ].	
  						
  				(beRecursive and: [ entryArray at: 4]) 
  					ifTrue: [ 
  						self 
  							startAt: entryRio
  							recursively: beRecursive 
  							select: selectBlock
  							into: results   
  					].	
   
  		].
  	
  	^ results!

Item was changed:
  ----- Method: RioFtp class>>defaultExecutive (in category 'as yet unclassified') -----
  defaultExecutive
  
+ 	^ RioFtpFileSystem new!
- 	^ RioFtpFileSystem!

Item was added:
+ ----- Method: RioFtpFileSystem>>ftpDo:ifError: (in category 'as yet unclassified') -----
+ ftpDo: aBlock ifError: errBlock
+  
+ 	[ self ftpDo: aBlock. 
+ 	  ] on: TelnetProtocolError do: errBlock !

Item was added:
+ ----- Method: RioFtpFileSystem>>mkpath: (in category 'as yet unclassified') -----
+ mkpath: aRio
+ 	self ftpDo: [ :client | super mkpath: aRio ]  !

Item was changed:
  ----- Method: RioFtpFileSystem>>makeNewRioOfClass:fromString: (in category 'as yet unclassified') -----
  makeNewRioOfClass: aRioClass fromString: aString
  
+ 	| exec path theUrl |
+ 
+ 	theUrl := aString asUrl.
- 	| rs exec |
- 	
- 	
- 	rs := aString readStream. 
- 
- 	"remove ftp://"
- 	rs next: 6.
- 	
- 	server := rs upTo: $/.
- 	
- 	user := server upTo: $@.
- 	user = server 
- 		ifTrue: [ user := 'anonymous' ]
- 		ifFalse: [ server := server allButFirst: user size + 1 ].
- 		
- 	exec := self.
- 	
- 	exec := self executiveForUser: user server: server.
  
+ 	path := String new writeStream.
+ 	
+ 	theUrl path do: [ :pathElem |
+ 		path nextPut: $/.
+ 		path nextPutAll: pathElem ].
+ 	
+ 	theUrl path: #().
+ 	
+ 	exec := self executiveForUrl: theUrl.
+ 
+ 	^ aRioClass executive: exec value: path contents.!
- 	^ aRioClass executive: exec value: rs remainingContents!

Item was added:
+ ----- Method: RioFtpFileSystem>>host (in category 'as yet unclassified') -----
+ host
+ 
+ 	^ url authority!

Item was added:
+ ----- Method: RioFtpFileSystem>>password: (in category 'as yet unclassified') -----
+ password: passwordString
+ 
+ 	| pwd |
+ 
+ 	self user = 'ftp' ifTrue: [ ^ self ].
+ 	
+ 	passwordString isEmpty ifTrue:[pwd := nil] ifFalse:[pwd := passwordString].
+ 	
+ 	self MCPasswordManager default passwordAt: url asString user: self user put: pwd.
+ !

Item was changed:
  RioKernel subclass: #Rio
  	instanceVariableNames: 'recursive rename adaptor binary'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'Rio-Grande'!
  
+ !Rio commentStamp: 'test 11/6/2008 00:05' prior: 0!
- !Rio commentStamp: 'kph 9/28/2007 00:45' prior: 0!
  Thinking out loud:
  
+ 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!!
- 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 murder 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.
- Experimental idea aims to add platform dependent items be added as run-time traits? See Rio>>startUp
- used in #areFilenamesCaseSensitive. Seems to work quite well. However due to the need to make Rio as backwardly compatible as possible, the trait's switching approach has been replaced by switching an abstract baseclass instead.
- 
- Note added 28-03-07 - Ok this experiment failed, wiser smalltalkers pointed out that this makes the package constantly dirty and wrotes the switch to the change log, also users/readers are likely to find this unexpected. The #executive abstraction covers the functionality instead.
- 
- #isFile does consider the possibility of a case insensitive filename comparison. I think this is a windows thing. So it is implemented accross the board in #= and #hash by the Abstract base class RioWin32 and so should work in things like Sets. The Unixish implementations use staight string comparison.
- 
- Note added 28-03-07 this is now handled by the rio's #executive, 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:
- Added a beRecursive mode which 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. 
- Is it worth caching the results of stat? It cant do any harm as long as the user is awaye that this data is cached and may be refreshed via #restat, and may need to 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. 
- 
- Default is now cached. Why not define 'cwd' as a global referring to the current working directory? This will be shot down in seconds by the purists!!
- Note added - 28-03-07 cwd is now available as a Class, enabling the readable form: Cwd / 'hello.txt' in code
- 
- So while we are being controversial, how can we incorporate the message eating null into the api? #ifDirectory and #ifFile return null if they are not so. This means that myFile is null or the readStream returned from #reading (or equiv). #ifFileDo: and #ifDirectoryDo: are for the purists.
- 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 assureNewFile).  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 and #deleteTree, #deleteTree seems a little dangerous, in just one method.
- '\' asRio deleteTree may not be a good idea!! Do we need a guard. Ok, lets set it so that #deleteTree will only work if the recursive flag is set, the recursive flag is reset which should be ok since the tree is no longer there.
- usage: aRio all deleteTree.
- 
- merged deleteTree into #rmdir
- 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 write.
- fileStream := aRio assureNewFile write.
- 
- And the block case, instead of implementing three methods.
- aRio readUsing: [ :str |  ].
- aRio appendUsing: [ :str |  ].
- myRio := aRio delete write out: [ :str | str, 'hello'; cr ].
- 
- we use #in:/#out: which ensures the stream is closed for us
- aRio write out: [ :str |  ].
- aRio write in: [ :str |  ].
  
+ 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 |  ].
- being clever/naughty I implemented FileStream close to return the stream's rio.
- this allows continuing with the rio after the cascade, or using the result in assigment.
- (myRio write < 'a bit' < 'abit more') close isFile ifTrue: [ 'it s a file' ]
- myRio := ((Rio new: 'test') write < 'a bit' < 'a bit more') close.
- myRio := (Rio new: 'test') write in: [ :w | w,'hello';cr ].
- myRio read contents.
- 
- We begin thinking about splitting Rio RioPrim into Rio and RioKernel, the latter being the minimal useful implementation for the KernelImage.
- 
- Let's try caching #readers or #writers. This may make code easier to write without method temporaries for streams derived from rio's. It isnt entirely necessary.
- myRio reader nextPut: a
- myRio reader close.
- Well, I tried verious forms of this and have decided that it is not a very good idea, simply because when you have finished using a stream you will want it closed and GC'ed you dont want it hanging around in some cache that you havent explicitly thought about. Using method temp vars for streams is the way to go.
- 
- Defined #reader: and #writer: to take a block.
- instead of aRio reader in: [ :str | ], you can write aRio reader: [ :inStream | ... ].
- instead of aRio writer out: [ :str | ], you can write aRio writer: [ :outStream | ... ].
- This is not really necessary, could remove #reader: and writer: assuming the code police can handle my adaption of #in: to this situation.
- 
- I have removed #append from rio, it would need an #append: for consistency. I think it is easy enough to do aRio writer: [ :out | out setToAppend. out ... ].
- 
- Being daring I am using Null as the error return from reader/writer, in Rio, though not in RioKernel.
- 
- I have worked to implement aStream copyTo: bStream as 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).
- 
- 20-03-07
- Created the #executive abstraction and removed the platform specific superclasses. The executives can be more versatile than simply different platform's native file systems. Shall support archives and remote file systems, and hopefully archives on remote file systems. 
- 
- 25-03-07
- Implemented and tested Win32 implementation, modelling Dos file Volumes as separate executives.
- Decided a comprehensive platform independent test framework is needed to be able to verify all platform scenarious.
  
+ 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.
+ 
+ RioFtpFileSystem executive depends upon MCPasswordManager to look after passwords.
- 29-03-07 Lazy initialialization of executive or not? Changed to not, on the basis that it is easier to debug if expliring a rio if you can see what the executive actually is rather than a nil.
  
- 
- 
  !

Item was changed:
  ----- Method: RioFtpFileSystem>>ftpOpenClient (in category 'as yet unclassified') -----
  ftpOpenClient
  
+ 	| loginSuccessful what client |
+ 	 
+ 	client := self FTPClient openOnHostNamed: self host.
- 	| loginSuccessful what |
- 	client
- 		ifNotNil: [client isConnected
- 			ifTrue: [^client]
- 			ifFalse: [client := nil]].
- 	client _ FTPClient openOnHostNamed: server.
  	loginSuccessful := false.
  	[loginSuccessful]
  		whileFalse: [
  			[loginSuccessful := true.
  			client loginUser: self user password: self password]
  				on: LoginFailedException
  				do: [:ex | 
+ 					what := UIManager default 
- 					passwordHolder _ nil.
- 					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 ].
- 					what = 1 ifFalse: [self error: 'Login failed.'. ^nil].
  					loginSuccessful := false]].
+  	
+ 	home := client pwd.
+ 	
-  
  	^client!

Item was added:
+ ----- Method: RioFtpFileSystem>>delete: (in category 'as yet unclassified') -----
+ delete: aRio
+ 	self ftpDo: [ :client | super delete: aRio ]  !

Item was changed:
  ----- Method: Rio>>adaptor (in category 'accessing') -----
  adaptor
  
+ 	^ adaptor ifNil: [ self defaultAdaptor ].  !
- 	^ adaptor!

Item was changed:
  ----- Method: Rio>>modificationTime (in category 'accessing stat') -----
  modificationTime
  
+ 	^ self stat modificationTime!
- ^ self stat modificationTime!

Item was changed:
  ----- Method: RioFtpFileSystem>>ftpParseEntry: (in category 'as yet unclassified') -----
  ftpParseEntry: ftpEntry
  	| tokens longy dateInSeconds thisYear thisMonth |
+ 	thisYear := Date today year.
+ 	thisMonth := Date today monthIndex.
+ 	tokens := ftpEntry findTokens: ' '. 
- 	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 _ 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)].
- 		[longy _ tokens at: 9.
- 		10 to: tokens size do: [:i | longy _ longy , ' ' , (tokens at: i)].
  		tokens at: 9 put: longy].
+ 	dateInSeconds := self
- 	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 added:
+ ----- Method: RioFtpFileSystem>>FTPClient (in category 'as yet unclassified') -----
+ FTPClient
+ 
+ 	^ FTPClientDebug!

Item was added:
+ ----- Method: RioFtpFileSystem>>dataAvailable (in category 'wrap socket') -----
+ dataAvailable
+ 
+ 	^ ftpClient dataSocket dataAvailable!

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

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

Item was added:
+ ----- Method: RioFtpFileSystem>>deleteDirectory: (in category 'as yet unclassified') -----
+ deleteDirectory: aRio
+ 
+ 	self ftpDo: [ :client | 
+ 		
+ 		client deleteDirectory: home, aRio asVmPathName.
+ 		
+ 	].
+ 
+ 	aRio statIsNowInvalid.!

Item was added:
+ ----- Method: Rio>>appender: (in category 'public file') -----
+ appender: block
+ 	 
+ 	 self writer setToAppend use: block
+ 	
+ !

Item was added:
+ ----- Method: RioFtpFileSystem>>isConnected (in category 'wrap socket') -----
+ isConnected
+ 
+ 	^ (ftpClient dataSocket ifNil: [ ^ false ]) isConnected!

Item was added:
+ ----- Method: RioFtpFileSystem>>isKeepAlive (in category 'as yet unclassified') -----
+ isKeepAlive
+ 
+ 	^ true!

Item was changed:
  ----- Method: Rio>>initialize (in category 'copying instanciation') -----
  initialize
  
+ 	value := ''.
+ 	recursive := false.!
- value := ''.
- recursive := false.!

Item was changed:
  ----- Method: Rio>>doesNotUnderstand: (in category 'adaptor wiring') -----
  doesNotUnderstand: aMessage
  
  	| anAdaptor |
  
+ 	anAdaptor := self adaptor.
- 	anAdaptor := adaptor ifNil: [ self defaultAdaptor ].  
  
  	 (anAdaptor respondsTo: aMessage selector) 
  		ifTrue: [ ^anAdaptor perform: aMessage selector withArguments: aMessage arguments ].
  	
  	^super doesNotUnderstand: aMessage!

Item was added:
+ ----- Method: RioFtpFileSystem>>mkdir: (in category 'as yet unclassified') -----
+ mkdir: aRio
+ 	self ftpDo: [ :client | super mkdir: aRio ]  !

Item was changed:
  ----- Method: Rio>>mkpath (in category 'public dir') -----
  mkpath
  
+     "this is like assureExistence"
-     "assureExistence lives here"
  
+ 	executive mkpath: self!
- 	self isDirectory ifTrue: [ ^self ].
- 	self parent mkpath.
- 	executive createDirectory: self  !

Item was added:
+ ----- Method: RioFtpFileSystem>>createDirectory: (in category 'as yet unclassified') -----
+ createDirectory: aRio
+ 
+ 	self ftpDo: [ :client | 
+ 		
+ 		client makeDirectory: home, aRio asVmPathName.
+ 		
+ 	].
+ 
+ 	aRio statIsNowInvalid.!

Item was changed:
  ----- Method: Rio>>fileSize (in category 'accessing stat') -----
  fileSize
  
+ 	^ self stat fileSize!
- ^self stat fileSize!

Item was changed:
+ RioExecutive subclass: #RioFtpFileSystem
+ 	instanceVariableNames: 'url home ftpClient isKeepAlive rw'
- Object subclass: #RioFtpFileSystem
- 	instanceVariableNames: 'client server passwordHolder directory user'
  	classVariableNames: 'Servers'
  	poolDictionaries: ''
  	category: 'Rio-Grande'!

Item was changed:
  ----- Method: Rio>>restat (in category 'accessing') -----
  restat
   
+ 	"when we restat, we populate the existing stat instance, because more than one rio may be sharing it"
+ 	
  	| full |
  	
  	full := self full.
+ 	full parent select: [ :e | e = full ifTrue: [ ^ stat copyFrom: e stat. ]. false. ].
- 	full parent select: [ :e | e = full ifTrue: [ ^ stat := e stat. ]. false. ].
  	
  	^ stat := nil.
  	
  "
  (Rio new: '')  myEntry.
   (Rio new: 'SqueakDebug.log') myEntry
  "!

Item was added:
+ ----- Method: RioFtpFileSystem>>receiveAvailableDataInto:startingAt: (in category 'wrap socket') -----
+ receiveAvailableDataInto: inBuffer startingAt: n
+ 
+ 	^ ftpClient dataSocket receiveAvailableDataInto: inBuffer startingAt: n!

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

Item was added:
+ ----- Method: RioFtpFileSystem>>executiveForUrl: (in category 'as yet unclassified') -----
+ executiveForUrl: aUrl
+ 
+ 	url := aUrl.
+ !

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

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

Item was added:
+ ----- Method: RioFtpFileSystem>>MCPasswordManager (in category 'as yet unclassified') -----
+ MCPasswordManager
+ 
+ 	^ MCPasswordManager!

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

Item was changed:
  ----- Method: Rio>>copyTo: (in category 'public file') -----
  copyTo: aPathOrRio
  
  	| outRio |
  
  	self validateIsFile.
  	 
  	^ (outRio := aPathOrRio asRio isBinary: self isBinary) writer: [ :out |
  	 	self reader: [ :in |
+ 			in copyTo: out size: self fileSize withProgress: 
- 			in copyTo: out withProgress: 
  				(self copyDescription, ' ', self asString, ' ', outRio copyResultDescription)
  		].
  	].
  
  !

Item was changed:
  ----- Method: RioFtpFileSystem>>ftpGetDirectory: (in category 'as yet unclassified') -----
  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 |
+ 
+ 	Transcript show: thisContext sender sender sender sender printString.
+ 
+ 	self ftpDo: [ :client |
- 	client := self ftpOpenClient.
- 	
- 	[
  		client changeDirectoryTo: dirString.
+ 		listing := client getDirectory ].	 
+ 		
- 		listing := client getDirectory] 		ensure: [self quit].
- 	
  	str := ReadStream on: listing.
  	
  	(str respondsTo: #contentsOfEntireFile) ifFalse: [^ #()].
  	
+ 	ftpEntries := str contentsOfEntireFile.
+ 	
+ 	Transcript cr; show: ftpEntries; cr.
+ 	
+ 	ftpEntries := ftpEntries findTokens: String crlf.
+ 	
- 	ftpEntries _ str contentsOfEntireFile findTokens: String crlf.
  	
  	^ ftpEntries 
  		collect:[:ftpEntry | self ftpParseEntry: ftpEntry ]
  		thenSelect: [:entry | entry notNil]!

Item was added:
+ ----- Method: RioFtpFileSystem>>rename:to: (in category 'as yet unclassified') -----
+ rename: aRio to: bRio
+ 	
+ 	self ftpDo: [ :client | client 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 added:
+ ----- Method: RioFtpFileSystem>>isFile: (in category 'as yet unclassified') -----
+ isFile: aRio
+ 
+ 	self ftpDo: [ :client | client getFileSize: home, aRio asVmPathName ] ifError: [ :ex | ^ false ].
+ 	 
+ 	^ true.!

Item was changed:
  ----- Method: Rio>>reader (in category 'public file') -----
  reader
  
+ 	^ self adaptor readStream!
- 	^ self readStream!

Item was added:
+ ----- Method: RioFtpFileSystem>>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: RioFtpFileSystem>>touch: (in category 'as yet unclassified') -----
+ touch: aRio
+ 
+ 	self ftpDo: [ :client |
+ 	
+ 		client putFileStreamContents: (WriteStream with: String new) as: home , aRio asVmPathName
+ 	
+ 	]!

Item was removed:
- ----- Method: RioFtpFileSystem>>executiveForUser:server: (in category 'as yet unclassified') -----
- executiveForUser: aUser server: aServer.
- 
- 	user := aUser.
- 	server := aServer.!

Item was removed:
- ----- Method: Rio>>copy (in category 'copying instanciation') -----
- copy
- 	
- 	^ self newFrom: self!

Item was removed:
- ----- Method: Rio>>exists (in category 'testing') -----
- exists
- 
- ^ self isDirectory or: [ self isFile ]!

Item was removed:
- ----- Method: Rio>>fileName (in category 'accessing fileName') -----
- fileName
- 
- 	^ stat ifNotNil: [ stat fileName ] ifNil: [ super fileName ]
-  !

Item was removed:
- ----- Method: PositionableStream>>copyTo:withProgress: (in category '*rio-grande') -----
- copyTo: out withProgress: label 
- 
- 	| buffer barPos  |
-  	
- 	buffer := (self peek isCharacter 
- 				ifTrue: [ String ] 
- 				ifFalse: [ out binary.    ByteArray ]) new: 50000.
- 
- 	label asString displayProgressAt: Sensor cursorPoint
- 		from: (barPos := 0) to: (self progressMax)
- 		during: [:bar |
- 				[ self atEnd ] whileFalse: [
- 				bar value: barPos.
- 				out nextPutAll: (self nextInto: buffer).
- 				barPos := self progress ].
- 		].!

Item was removed:
- ----- Method: RioFtpFileSystem class>>initializeServers (in category 'as yet unclassified') -----
- initializeServers
- 	
- 	Servers := Set new !

Item was removed:
- ----- Method: RioFtpFileSystem class>>freeSomeSpace (in category 'as yet unclassified') -----
- freeSomeSpace 
- 	
- 	self initializeServers!

Item was removed:
- ----- Method: RioFtpFileSystem class>>initialize (in category 'as yet unclassified') -----
- initialize 
- 	
- 	self initializeServers!



More information about the Packages mailing list