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

squeak-dev-noreply at lists.squeakfoundation.org squeak-dev-noreply at lists.squeakfoundation.org
Mon Nov 10 17:00:45 UTC 2008


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

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

Name: Rio-Grande-kph.45
Author: kph
Time: 10 November 2008, 5:00:42 pm
UUID: 258ae1d9-1875-4e89-9dfd-60082d7809fc
Ancestors: Rio-Grande-kph.44

Re-architected to be cleaner, remove dnus etc

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

Item was added:
+ ----- Method: RioHttpExecutive>>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:
  ----- Method: Rio>>archive (in category 'public modes') -----
  archive
  
+ 	^ self zip!
- 	^ self new setModeToZip!

Item was added:
+ ----- Method: Rio>>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.
+ 		
+ 	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: RioArchive>>archive (in category 'accessing') -----
+ archive
+ 
+ 	^ executive archive!

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

Item was added:
+ ----- Method: Rio>>addTree: (in category 'directory/container actions') -----
+ addTree: aDir
+ 
+ 	| base newAddition |
+ 	
+ 	self validateIsContainer.
+ 	aDir validateIsDirectory.
+ 	
+ 	newAddition := self add: aDir fromBase: (base := aDir parent). 
+ 	
+ 	self addAll: (aDir all entries) fromBase: base.
+ 	
+ 	^ newAddition
+ 	 !

Item was added:
+ ----- Method: RioArchive>>add:fromBase: (in category 'public') -----
+ add: aFileOrDir fromBase: aBaseDirectory
+ 
+ 	"I am an archive, add the file or create directory using aBaseDirectory 
+ 	 as the base reference."
+ 
+ 	| localFileName |
+ 	
+ 	self validateIsContainer.
+ 	
+ 	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: Rio>>gzip (in category 'public modes') -----
  gzip
  
+ 	^ RioGzip newFrom: self!
- 	^ self copy setModeToGzip!

Item was added:
+ ----- Method: Rio>>beBinary (in category 'public modes') -----
+ beBinary
+ 
+  binary := true!

Item was added:
+ Rio subclass: #RioDir
+ 	instanceVariableNames: ''
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'Rio-Grande'!
+ 
+ !RioDir commentStamp: 'kph 4/12/2007 07:44' prior: 0!
+ Could mode mkdir and mkpath into this adaptor.!

Item was changed:
  ----- Method: Rio>>rename (in category 'public modes') -----
  rename
  
+ 	^ self copy beRenaming  !
- 	^ self copy setModeToRenaming  !

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

Item was changed:
  ----- Method: RioFtpExecutive>>receiveDataSignallingTimeout:into:startingAt: (in category 'wrap socket') -----
  receiveDataSignallingTimeout: timeout
  					into: inBuffer startingAt: inNextToWrite
  
+ 	^ client dataSocket receiveDataSignallingTimeout: timeout
- 	^ ftpClient dataSocket receiveDataSignallingTimeout: timeout
  					into: inBuffer startingAt: inNextToWrite!

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

Item was added:
+ ----- Method: RioGzip>>basicReader (in category 'streams') -----
+ basicReader
+ 
+ 	self validateIsFile. 
+ 	
+ 	^ GZipReadStream on: (super basicReader).!

Item was changed:
  RioRemoteExecutive subclass: #RioHttpExecutive
  	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'Rio-Grande'!
+ 
+ !RioHttpExecutive commentStamp: 'kph 11/10/2008 05:36' prior: 0!
+ placeholder!

Item was added:
+ ----- Method: Rio>>commit (in category 'directory/container actions') -----
+ commit
+ 
+  !

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

Item was added:
+ ----- Method: RioGzip>>decompress (in category 'streams') -----
+ decompress
+ 
+ 	^ self copyTo: ((Rio new: self asString) ext: '') 
+ !

Item was added:
+ ----- Method: RioArchive>>commit (in category 'public') -----
+ commit
+ 
+ 	"Catch attempts to overwrite existing zip file"
+ 	(self archive canWriteToFileNamed: self asString)
+ 		ifFalse: [ ^ self error: 'a member of this archive is using this file: ',  self  ].
+ 	
+ 	self writer: [ :stream |
+ 		self archive writeTo: stream.
+ 	].!

Item was changed:
  ----- 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 ] 
- 				ifTrue: [ out ascii.  String ] 
  				ifFalse: [ out binary. ByteArray ]) new: 50000.
  	
  	out nextPut: first.
  
  	label asString displayProgressAt: Sensor cursorPoint
  		from: (barPos := 0) to: (aSize)
  		during: [:bar |
  				[ self atEnd ] whileFalse: [
  				bar value: barPos.
  				out nextPutAll: (read := self nextInto: buffer).
  				barPos := barPos + read size ].
  		].!

Item was added:
+ ----- Method: Rio>>beRenaming (in category 'public modes') -----
+ beRenaming
+ 
+ 	rename := true!

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

Item was added:
+ ----- Method: RioArchive>>setRio: (in category 'accessing') -----
+ setRio: aRio
+ 
+ 	super setRio: aRio.
+ 	aRio executive: (RioArchiveExecutive file: aRio copy).
+ 	aRio value: ''. "aRio executive root value."!

Item was added:
+ ----- Method: Rio>>commit: (in category 'directory/container actions') -----
+ commit: monadicBlock
+ 
+  	 monadicBlock value; self.
+ 	 self commit.!

Item was added:
+ ----- Method: RioArchive>>validExtensions (in category 'validation') -----
+ validExtensions
+ 
+ 	^ #('zip' 'mcz')!

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

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

Item was added:
+ ----- Method: Rio>>writeStream (in category 'adaptor') -----
+ writeStream
+ 
+ 	| writer |
+ 
+ 	writer := self basicWriter ifNil: [ ^ nil ].
+ 	
+ 	self isBinary ifTrue: [ writer binary ].
+ 	
+ 	^ writer!

Item was added:
+ ----- Method: RioGzip>>readStream (in category 'streams') -----
+ readStream
+ 
+ 	| str |
+ 	self validateGzip.
+ 	
+ 	str := super basicReader.
+ 	
+ 	self isBinary ifTrue: [ str binary ].
+ 	
+ 	^ self readerClass on: str.
+ 	 !

Item was added:
+ ----- Method: RioGzip>>copyDescription (in category 'streams') -----
+ copyDescription
+ 
+  ^ 'Decompressing'!

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

Item was added:
+ ----- Method: RioArchive>>comment: (in category 'public') -----
+ comment: aComment
+ 
+ 	self archive zipFileComment: aComment!

Item was added:
+ ----- Method: RioArchive>>writeStream (in category 'public') -----
+ writeStream
+ 
+ 	^ self file writeStream!

Item was changed:
  ----- Method: RioFtpExecutive>>rioClass (in category 'as yet unclassified') -----
  rioClass
  
+ 	^ Rio!
- 	^ RioFtp!

Item was added:
+ ----- Method: RioGzip>>compress (in category 'streams') -----
+ compress
+ 
+ 	^ self binary basic copyTo: (self + '.gz') gzip.
+ 	
+  !

Item was added:
+ ----- Method: RioGzip>>readerClass (in category 'streams') -----
+ readerClass
+ 	
+ 	^ GZipReadStream !

Item was changed:
  ----- Method: Rio>>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.
+ 				 self entries do:  [:d | d beRecursive delete ] ].
- 				 self entries do:  [:d | d setModeToRecursive delete ] ].
  
  	executive deleteDirectory: self
  	!

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

Item was changed:
  ----- Method: RioRemoteExecutive>>setUrl: (in category 'as yet unclassified') -----
  setUrl: aUrl
  
  	url := aUrl.
  !

Item was added:
+ ----- Method: RioArchive>>setArchive: (in category 'accessing') -----
+ setArchive: anArchiveManager
+ 
+ 	executive setArchive: anArchiveManager.
+ 	
+ !

Item was changed:
  ----- Method: Rio>>all (in category 'public modes') -----
  all
+ 	^ self copy beRecursive!
- 	^ self copy setModeToRecursive!

Item was added:
+ ----- Method: RioGzip>>writerClass (in category 'streams') -----
+ writerClass
+ 	
+ 	^ GZipWriteStream !

Item was changed:
  ----- Method: RioFtpExecutive>>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 ] ] ].
- 		ensure: [  (isKeepAlive := tmp) ifFalse: [ ftpClient ifNotNil: [ ftpClient quit ] ] ].
  	
  	^ result!

Item was changed:
  ----- Method: Rio>>recursively (in category 'public modes') -----
  recursively
+ 	^ self copy beRecursive!
- 	^ self new setModeToRecursive!

Item was added:
+ ----- Method: Rio>>addAll: (in category 'directory/container actions') -----
+ addAll: aCollectionOfFiles
+ 	
+ 	aCollectionOfFiles do: [ :each | self add: each ]!

Item was changed:
  RioRemoteExecutive subclass: #RioFtpExecutive
+ 	instanceVariableNames: 'home isKeepAlive rw ftpClient'
- 	instanceVariableNames: 'home isKeepAlive rw'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'Rio-Grande'!

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

Item was added:
+ ----- Method: Rio>>readForm (in category 'adaptor') -----
+ readForm
+ 
+ 	^ ImageReadWriter formFromFileNamed: self asString !

Item was added:
+ ----- Method: Rio>>validateIsContainer (in category 'directory/container actions') -----
+ validateIsContainer
+ 
+ 	self validateIsDirectory
+ 	 !

Item was changed:
  ----- Method: Rio>>zip (in category 'public modes') -----
  zip
  
+ 	^ (RioArchive on: self) setArchive: ZipArchive new; yourself!
- 	^ self copy setModeToZip!

Item was changed:
  ----- Method: RioFtpExecutive>>dataAvailable (in category 'wrap socket') -----
  dataAvailable
  
+ 	^ client dataSocket dataAvailable!
- 	^ ftpClient dataSocket dataAvailable!

Item was added:
+ ----- Method: RioArchive>>validateIsContainer (in category 'validation') -----
+ validateIsContainer
+ 
+ 	(self validExtensions includes: self file ext) ifFalse: [ ^self error: 'wrong extension for a zip archive' ]. 
+ 	 !

Item was added:
+ ----- Method: RioGzip>>validateGzip (in category 'validation & errors') -----
+ validateGzip
+ 
+ 	(self validExtensions includes: self ext) ifFalse: [ ^self error: 'wrong extension for a gzip file' ]. 
+  	!

Item was added:
+ ----- Method: Rio>>add: (in category 'directory/container actions') -----
+ add: aFile 
+ 	
+ 	self validateIsDirectory.
+ 	aFile validateIsFile.
+ 	 
+ 	^ aFile copyTo: self / aFile fileName
+ 	 !

Item was added:
+ ----- Method: RioGzip>>copyResultDescription (in category 'streams') -----
+ copyResultDescription
+ 
+  ^ 'Compressed with gzip'!

Item was added:
+ ----- Method: RioGzip>>validExtensions (in category 'streams') -----
+ validExtensions
+ 
+ ^ #( 'gz' )!

Item was added:
+ ----- Method: RioArchive>>add: (in category 'public') -----
+ add: aFile 
+ 	 
+ 	self validateIsContainer.
+ 	aFile validateIsFile.
+ 	
+ 	self archive addFile: aFile full asString as: aFile fileName.
+ 	
+ 	!

Item was changed:
  ----- Method: Rio>>auto (in category 'public modes') -----
  auto
  
+ 	self ext = 'gz' ifTrue: [ ^ self gzip ].
+ 	
+ 	^ self copy!
- 	^ self copy setModeAutomatically !

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

Item was changed:
  ----- Method: Rio>>binary (in category 'public modes') -----
  binary
  
+ 	^ self copy beBinary  !
- 	^ self copy setModeToBinary  !

Item was added:
+ ----- Method: RioArchive class>>on: (in category 'as yet unclassified') -----
+ on: aRio
+ 
+ 	^ self executive: (RioArchiveExecutive file: aRio) value: ''.!

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

Item was added:
+ ----- Method: RioGzip>>writeStream (in category 'streams') -----
+ writeStream
+ 
+ 	| str |
+ 	self validateGzip.
+  	
+ 	str := self writerClass on: (super writeStream ifNil: [ ^ nil ]).
+ 	self setFileTypeToObject.
+ 
+ 	^ str!

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

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

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

Item was added:
+ ----- Method: Rio>>readStream (in category 'adaptor') -----
+ readStream
+ 
+ 	| reader |
+ 
+ 	reader :=  self basicReader ifNil: [ ^ nil ].
+ 	
+ 	self isBinary ifTrue: [ reader binary ].
+ 	
+ 	^ reader!

Item was added:
+ ----- Method: Rio>>basic (in category 'public modes') -----
+ basic
+ 
+ 	^ Rio newFrom: self!

Item was added:
+ ----- Method: Rio>>beRecursive (in category 'public modes') -----
+ beRecursive
+ 
+ 	recursive := true!

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

Item was changed:
  ----- Method: RioFtpExecutive>>ftpOpenForRead: (in category 'as yet unclassified') -----
  ftpOpenForRead: aRio
  
  	self ftpClient openPassiveDataConnection.
  	self ftpClient sendCommand: 'RETR ', home , aRio asVmPathName.
  	
+ 	[client checkResponse]
- 	[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>>tar (in category 'public modes') -----
  tar
  
+ 	^ (RioArchive on: self) setArchive: TarArchive new; yourself!
- 	^ self copy setModeToTar!

Item was added:
+ Rio subclass: #RioArchive
+ 	instanceVariableNames: ''
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'Rio-Grande'!

Item was added:
+ Rio subclass: #RioGzip
+ 	instanceVariableNames: ''
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'Rio-Grande'!
+ 
+ !RioGzip commentStamp: 'kph 3/16/2007 08:06' prior: 0!
+ In using gzip rio expects that if you write text to the file you should read text from the file. 
+ 
+ The 3.9 implemementation of InflateStream blindly sets the readStream to binary. Although its output buffer is created using #species new: in an attempt to make the output in the correct form in practice this would always result in a ByteArray.
+ 
+ A small fix to InflateStream #on:, checks the #binary setting before is is 'blindly set' and initializes the output collection to be a String is it is not binary.
+ 
+ In #on:from:to: the collection is initialized to be a buffer being the same species as itself if set in #on:
+ 
+ !

Item was removed:
- ----- Method: RioAdaptorGzip>>copyResultDescription (in category 'streams') -----
- copyResultDescription
- 
-  ^ 'Compressed with gzip'!

Item was removed:
- ----- Method: RioAdaptorGzip>>validExtensions (in category 'streams') -----
- validExtensions
- 
- ^ #( 'gz' )!

Item was removed:
- ----- Method: RioAdaptorArchive>>writeStream (in category 'public') -----
- writeStream
- 
- 	^ self file writeStream!

Item was removed:
- ----- Method: RioAdaptorGzip>>readerClass (in category 'streams') -----
- readerClass
- 	
- 	^ GZipReadStream !

Item was removed:
- ----- Method: RioAdaptor>>readStream (in category 'as yet unclassified') -----
- readStream
- 
- 	| reader |
- 
- 	reader :=  rio basicReader ifNil: [ ^ nil ].
- 	
- 	rio isBinary ifTrue: [ reader binary ].
- 	
- 	^ reader!

Item was removed:
- ----- Method: RioAdaptor>>readForm (in category 'as yet unclassified') -----
- readForm
- 
- 	^ ImageReadWriter formFromFileNamed: rio asString !

Item was removed:
- RioAdaptor subclass: #RioAdaptorGzip
- 	instanceVariableNames: ''
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'Rio-Grande'!
- 
- !RioAdaptorGzip commentStamp: 'kph 3/16/2007 08:06' prior: 0!
- In using gzip rio expects that if you write text to the file you should read text from the file. 
- 
- The 3.9 implemementation of InflateStream blindly sets the readStream to binary. Although its output buffer is created using #species new: in an attempt to make the output in the correct form in practice this would always result in a ByteArray.
- 
- A small fix to InflateStream #on:, checks the #binary setting before is is 'blindly set' and initializes the output collection to be a String is it is not binary.
- 
- In #on:from:to: the collection is initialized to be a buffer being the same species as itself if set in #on:
- 
- !

Item was removed:
- ----- Method: Rio>>setModeToTar (in category 'public modes') -----
- setModeToTar
- 
- 	adaptor := RioAdaptorArchive rio: self archive: TarArchive new.!

Item was removed:
- ----- Method: RioAdaptorDir>>addAll: (in category 'as yet unclassified') -----
- addAll: aCollectionOfFiles
- 	
- 	aCollectionOfFiles do: [ :each | self add: each ]!

Item was removed:
- ----- Method: Rio>>respondsTo: (in category 'adaptor wiring') -----
- respondsTo: aSymbol
- 	
- 	^ (self class canUnderstand: aSymbol) or: [ self adaptor class canUnderstand: aSymbol ]!

Item was removed:
- ----- Method: Rio>>setModeAutomatically (in category 'public modes') -----
- setModeAutomatically 
- 
- 	self ext = 'gz' ifTrue: [ self setModeToGzip ]!

Item was removed:
- ----- Method: RioAdaptorGzip class>>validExtensions (in category 'as yet unclassified') -----
- validExtensions
- 
- ^ #( 'gz' )!

Item was removed:
- ----- Method: RioAdaptorDir>>addAll:fromBase: (in category 'as yet unclassified') -----
- addAll: aCollection fromBase: aDirectory
- 
- 	 aCollection do: [ :each | self add: each fromBase: aDirectory ]!

Item was removed:
- ----- Method: RioFtpExecutive>>rootString (in category 'as yet unclassified') -----
- rootString
- 
- 	^ '/'!

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

Item was removed:
- Rio subclass: #RioHttp
- 	instanceVariableNames: ''
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'Rio-Grande'!

Item was removed:
- Rio subclass: #RioFtp
- 	instanceVariableNames: ''
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'Rio-Grande'!

Item was removed:
- ----- Method: RioAdaptor class>>rio: (in category 'as yet unclassified') -----
- rio: aRio
- 
- 	^ (self new) 
- 		setRio: aRio; 
- 		yourself!

Item was removed:
- ----- Method: RioAdaptorDir>>add: (in category 'as yet unclassified') -----
- add: aFile 
- 	
- 	self validate.
- 	aFile validateIsFile.
- 	 
- 	^ aFile copyTo: rio / aFile fileName
- 	 !

Item was removed:
- ----- Method: RioAdaptorArchive>>archive (in category 'accessing') -----
- archive
- 
- 	^ rio executive archive!

Item was removed:
- ----- Method: RioAdaptorArchive>>add: (in category 'public') -----
- add: aFile 
- 	 
- 	self validate.
- 	aFile validateIsFile.
- 	
- 	self archive addFile: aFile full asString as: aFile fileName.
- 	
- 	!

Item was removed:
- ----- Method: RioAdaptorArchive>>add:fromBase: (in category 'public') -----
- add: aFileOrDir fromBase: aBaseDirectory
- 
- 	"I am an archive, add the file or create directory using aBaseDirectory 
- 	 as the base reference."
- 
- 	| localFileName |
- 	
- 	self validate.
- 	
- 	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 removed:
- ----- Method: RioFtpExecutive>>host (in category 'as yet unclassified') -----
- host
- 
- 	^ url authority!

Item was removed:
- ----- Method: RioAdaptorGzip>>writeStream (in category 'streams') -----
- writeStream
- 
- 	| str |
- 	self validate.
-  	
- 	str := self writerClass on: (super writeStream ifNil: [ ^ nil ]).
- 	rio setFileTypeToObject.
- 
- 	^ str!

Item was removed:
- ----- Method: RioFtpExecutive>>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 removed:
- ----- Method: RioAdaptorDir>>validate (in category 'as yet unclassified') -----
- validate
- 
- 	rio validateIsDirectory
- 	 !

Item was removed:
- ----- Method: RioAdaptorGzip>>basicReader (in category 'streams') -----
- basicReader
- 
- 	self validate.
- 	
- 	^ GZipReadStream on: (super basicReader).!

Item was removed:
- ----- Method: RioAdaptorGzip>>decompress (in category 'streams') -----
- decompress
- 
- 	^ rio binary copyTo: ((Rio new: rio asString) ext: '') 
- !

Item was removed:
- ----- Method: RioAdaptorArchive>>commit (in category 'public') -----
- commit
- 
- 	"Catch attempts to overwrite existing zip file"
- 	(self archive canWriteToFileNamed: rio asString)
- 		ifFalse: [ ^ self error: 'a member of this archive is using this file: ',  rio  ].
- 	
- 	rio writer: [ :stream |
- 		self archive writeTo: stream.
- 	].!

Item was removed:
- RioAdaptorDir subclass: #RioAdaptorArchive
- 	instanceVariableNames: 'archive'
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'Rio-Grande'!

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

Item was removed:
- ----- Method: Rio>>setModeToRenaming (in category 'public modes') -----
- setModeToRenaming
- 
- 	rename := true!

Item was removed:
- ----- Method: RioAdaptorArchive>>validate (in category 'validation') -----
- validate
- 
- 	(self validExtensions includes: self file ext) ifFalse: [ ^self error: 'wrong extension for a zip archive' ]. 
- 	 !

Item was removed:
- ----- Method: RioFtpExecutive>>setUrl: (in category 'as yet unclassified') -----
- setUrl: aUrl
- 
- 	url := aUrl.
- !

Item was removed:
- ----- Method: RioAdaptorArchive>>validExtensions (in category 'validation') -----
- validExtensions
- 
- 	^ #('zip' 'mcz')!

Item was removed:
- ----- Method: RioHttpExecutive class>>makeNewRioFrom: (in category 'as yet unclassified') -----
- makeNewRioFrom: aString
- 
- 	| 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.
- 
- 	^ exec rioClass executive: exec value: path contents.!

Item was removed:
- ----- Method: Rio>>defaultAdaptor (in category 'private') -----
- defaultAdaptor
- 
- 	self isDirectory ifTrue: [ ^ RioAdaptorDir rio: self ].
- 	
- 	^ RioAdaptor rio: self!

Item was removed:
- ----- Method: RioAdaptorArchive class>>rio:archive: (in category 'as yet unclassified') -----
- rio: aRio archive: anArchive
- 
- 	^ (super rio: aRio) 
- 		setArchive: anArchive;
- 		yourself!

Item was removed:
- ----- Method: RioFtp class>>canInstanciate: (in category 'as yet unclassified') -----
- canInstanciate: aPathString
- 
- ^ aPathString beginsWith: 'ftp:'!

Item was removed:
- ----- Method: RioAdaptorDir>>add:fromBase: (in category 'as yet unclassified') -----
- add: aFileOrDir fromBase: aBaseDirectory
- 
- 	"I am a directory, add the file or create directory using aBaseDirectory 
- 	 as the base reference."
- 
- 	| newRio |
- 	
- 	self validate.
- 		
- 	newRio := rio / (aFileOrDir linearRelativeTo: aBaseDirectory).
- 	
- 	aFileOrDir isFile ifTrue: [ 
- 		newRio parent ifAbsentDo: [ :newPath | newPath mkpath ].
- 		^ aFileOrDir copyTo: newRio 
- 	].
- 	
- 	aFileOrDir isDirectory ifTrue: [ ^ newRio mkpath ]. 
- 	
- !

Item was removed:
- ----- Method: RioAdaptorArchive>>comment: (in category 'public') -----
- comment: aComment
- 
- 	self archive zipFileComment: aComment!

Item was removed:
- ----- Method: RioAdaptorGzip>>readStream (in category 'streams') -----
- readStream
- 
- 	self validate.
- 	
- 	^ self readerClass on: (super readStream).!

Item was removed:
- ----- Method: RioAdaptorGzip>>copyDescription (in category 'streams') -----
- copyDescription
- 
-  ^ 'Decompressing'!

Item was removed:
- ----- Method: RioAdaptorDir>>addTree: (in category 'as yet unclassified') -----
- addTree: aDir
- 
- 	| base newAddition |
- 	
- 	self validate.
- 	aDir validateIsDirectory.
- 	
- 	newAddition := self add: aDir fromBase: (base := aDir parent). 
- 	
- 	self addAll: (aDir all entries) fromBase: base.
- 	
- 	^ newAddition
- 	 !

Item was removed:
- ----- Method: RioAdaptorArchive>>file (in category 'public') -----
- file
- 
- 	^ rio executive file  !

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

Item was removed:
- ----- Method: RioHttp class>>canInstanciate: (in category 'as yet unclassified') -----
- canInstanciate: aPathString
- 
- ^ aPathString beginsWith: 'http:'!

Item was removed:
- RioAdaptor subclass: #RioAdaptorDir
- 	instanceVariableNames: ''
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'Rio-Grande'!
- 
- !RioAdaptorDir commentStamp: 'kph 4/12/2007 07:44' prior: 0!
- Could mode mkdir and mkpath into this adaptor.!

Item was removed:
- ----- Method: RioAdaptorGzip>>compress (in category 'streams') -----
- compress
- 
- 	^ rio binary setModeToNoAdaptor copyTo: (rio + '.gz') setModeToGzip.
- 	
-  !

Item was removed:
- ----- Method: Rio>>setModeToBinary (in category 'public modes') -----
- setModeToBinary
- 
-  binary := true!

Item was removed:
- ----- Method: RioAdaptor>>setRio: (in category 'as yet unclassified') -----
- setRio: aRio
- 
- 	rio := aRio!

Item was removed:
- Object subclass: #RioAdaptor
- 	instanceVariableNames: 'rio'
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'Rio-Grande'!

Item was removed:
- ----- Method: RioAdaptorArchive>>setArchive: (in category 'accessing') -----
- setArchive: anArchiveManager
- 
- 	rio executive setArchive: anArchiveManager.
- 	
- !

Item was removed:
- ----- Method: RioAdaptorDir>>commit (in category 'as yet unclassified') -----
- commit
- 
-  !

Item was removed:
- ----- Method: RioAdaptorGzip>>writerClass (in category 'streams') -----
- writerClass
- 	
- 	^ GZipWriteStream !

Item was removed:
- ----- Method: Rio>>setModeToZip (in category 'public modes') -----
- setModeToZip
- 
- 	adaptor := RioAdaptorArchive rio: self archive: ZipArchive new.	
- !

Item was removed:
- ----- Method: RioAdaptorDir>>commit: (in category 'as yet unclassified') -----
- commit: monadicBlock
- 
-  	 monadicBlock value; self.
- 	 self commit.!

Item was removed:
- ----- Method: Rio>>setModeToGzip (in category 'public modes') -----
- setModeToGzip
- 
- 	adaptor := RioAdaptorGzip rio: self
- 	!

Item was removed:
- ----- Method: RioAdaptor>>writeStream (in category 'as yet unclassified') -----
- writeStream
- 
- 	| writer |
- 
- 	writer :=  rio basicWriter ifNil: [ ^ nil ].
- 	
- 	rio isBinary ifTrue: [ writer binary ].
- 	
- 	^ writer!

Item was removed:
- ----- Method: RioAdaptorArchive>>setRio: (in category 'accessing') -----
- setRio: aRio
- 
- 	super setRio: aRio.
- 	aRio executive: (RioArchiveExecutive file: aRio copy).
- 	aRio value: ''. "aRio executive root value."!

Item was removed:
- ----- Method: Rio>>setModeToRecursive (in category 'public modes') -----
- setModeToRecursive
- 
- 	recursive := true!

Item was removed:
- ----- Method: Rio>>setModeToNoAdaptor (in category 'public modes') -----
- setModeToNoAdaptor
- 
- 	adaptor := nil
- 	!

Item was removed:
- ----- Method: RioAdaptorGzip>>validate (in category 'validation & errors') -----
- validate
- 
- 	(self validExtensions includes: rio ext) ifFalse: [ ^self error: 'wrong extension for a gzip file' ]. 
-  	!



More information about the Packages mailing list