[Pkg] Rio: Rio-Kernel-kph.84.mcz

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


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

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

Name: Rio-Kernel-kph.84
Author: kph
Time: 7 November 2008, 2:57:49 am
UUID: 655d748d-c9e6-4a0e-b2e3-ec6ff6acb34f
Ancestors: Rio-Kernel-kph.83

ftp support complete(?)

=============== Diff against Rio-Kernel-kph.83 ===============

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

Item was changed:
  ----- Method: RioKernel>>basicWriter (in category 'public file') -----
  basicWriter
  
+ 	^ executive basicWriter: self!
- 	^ self class fileStreamClass new open: self forWrite: true 
- 	!

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

Item was changed:
  ----- Method: RioKernel>>setExecutive:value: (in category 'as yet unclassified') -----
  setExecutive: e value: aRef
  
  	"create a fully initialized rio"
  
  	executive := e.
+ 	self value: aRef.
- 	self from: aRef.
  	
  	^ self !

Item was added:
+ ----- Method: RioExecutive>>mkdir: (in category 'as yet unclassified') -----
+ mkdir: aRio
+ 
+ 	aRio isDirectory ifTrue: [ ^ self error: 'directory already exists' ].
+ 	self createDirectory: aRio  !

Item was added:
+ ----- Method: SocketStream>>copyTo: (in category '*rio-kernel') -----
+ copyTo: out
+ 	
+ 	self isBinary ifTrue: [ out binary ].
+ 		
+ 	[self atEnd] whileFalse:
+ 		[ self receiveAvailableData.
+ 		  out nextPutAll: self nextAllInBuffer.
+ 		  ].
+ !

Item was changed:
  ----- Method: RioLocalDosFileSystem>>drive (in category 'accessing') -----
  drive 
  
+ 	^ self rootString first: 2!
- 	^ root first: 2!

Item was changed:
  ----- Method: RioLocalDosFileSystem>>initializeDefault (in category 'as yet unclassified') -----
  initializeDefault
    
+ 	self setRootString: (self primImagePath first: 3);
- 	self setRoot: (self primImagePath first: 3);
  		setDefault: self getDefaultDirectory.
  
  	Volumes add: self.!

Item was added:
+ ----- Method: RioExecutive>>basicWriter: (in category 'as yet unclassified') -----
+ basicWriter: aRio
+ 
+ 	^ self class fileStreamClass new open: aRio forWrite: true 
+ 	!

Item was changed:
  ----- Method: RioLocalFileSystem>>printId (in category 'printing') -----
  printId
  
+ 	^ rootString!
- 	^ root!

Item was changed:
  ----- Method: RioStat>>invalidate (in category 'as yet unclassified') -----
  invalidate
  	
- 	dir := nil.
  	array := nil.!

Item was changed:
  ----- Method: RioLocalDosFileSystem>>isRoot: (in category 'as yet unclassified') -----
  isRoot: aRioOrString
  
+ 	aRioOrString value size = self rootString size ifTrue: [ ^ super isRoot: aRioOrString ].
- 	aRioOrString value size = root size ifTrue: [ ^ super isRoot: aRioOrString ].
  	
+ 	^ (aRioOrString value, self pathDelimiter) = self rootString!
- 	^ (aRioOrString value, self pathDelimiter) = root!

Item was added:
+ ----- Method: RioExecutive>>pathDelimiterChar (in category 'as yet unclassified') -----
+ pathDelimiterChar
+  
+ 	^ $/
+ !

Item was changed:
  ----- Method: RioKernel>>value: (in category 'as yet unclassified') -----
  value: aStringable
  		
   	 value := executive importValue: aStringable asString.
  	
+ !
- 	 !

Item was changed:
  ----- Method: RioKernel>>stat (in category 'stat') -----
  stat
  
  	| full |
  
  	(stat notNil and: [ stat isValid ]) ifTrue: [ ^ stat ].
+ 
+ 
- 	
  	full := self full.
+ 	(self newFrom: full path) select: [ :e | 
+ 		
+ 		e = full ifTrue: [ ^ stat ifNil: [ e stat ] ifNotNil: [ stat copyFrom: e stat. ] ]. 
+ 			
+ 	false. 
- 	full parent select: [ :e | e = full ifTrue: [ ^ stat := e stat. ]. false. ].
- 	
- 	^ stat := nil.
  	
+ 	].
+ 	
+ 	^ stat := nil.
+ 	
  "
+  (Rio new: '')  stat.
- (Rio new: '')  stat.
   (Rio new: 'SqueakDebug.log') stat
  "!

Item was added:
+ ----- Method: RioExecutive>>importValue: (in category 'executive actions') -----
+ importValue: path
+  
+ 	path isEmpty ifTrue: [  ^ '' ].
+ 	
+ 	(self isRoot: path) ifTrue: [ ^ self rootString ].
+ 	
+  	(path last = self pathDelimiter first) ifTrue: [ ^ path allButLast ].
+ 	
+ 	^path!

Item was added:
+ ----- Method: RioLocalFileSystem>>rootString (in category 'accessing') -----
+ rootString
+ 
+ 	^ rootString!

Item was added:
+ ----- Method: RioExecutive>>isFile: (in category 'as yet unclassified') -----
+ isFile: aRio 
+ 
+ 	^ (aRio stat ifNil: [ ^ false ]) isFile
+ !

Item was added:
+ Object subclass: #RioExecutive
+ 	instanceVariableNames: ''
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'Rio-Kernel'!

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

Item was changed:
  ----- Method: PositionableStream>>copyTo: (in category '*rio-kernel') -----
  copyTo: out
  		
+ 	| buffer first |
- 	| buffer |
   	
+ 	self atEnd ifTrue: [ ^ self ].
+ 	
+ 	first := self next.
+ 	
+ 	buffer := (first isCharacter 
- 	buffer := (self peek isCharacter 
  				ifTrue: [ String ] 
+ 				ifFalse: [ out binary. ByteArray ]) new: 50000.
+ 	
+ 	out nextPut: first.
- 				ifFalse: [ out binary.    ByteArray ]) new: 50000.
  
  	[self atEnd] whileFalse:
  		[out nextPutAll: (self nextInto: buffer)].
  !

Item was changed:
  ----- Method: RioLocalDosFileSystem>>executiveForVolume: (in category 'accessing') -----
  executiveForVolume: requestedRoot
   
  	^ Volumes 
  		detect: [ :i | i isRoot: requestedRoot ] 
+ 		ifNone: [ Volumes add: (self class basicNew setRootString: requestedRoot; setDefault: nil; yourself) ]!
- 		ifNone: [ Volumes add: (self class basicNew setRoot: requestedRoot; setDefault: nil; yourself) ]!

Item was added:
+ ----- Method: RioExecutive>>rootString (in category 'as yet unclassified') -----
+ rootString
+ 
+ 	^ self subclassResponsibility!

Item was changed:
  ----- Method: RioKernel>>fileName (in category 'accessing') -----
  fileName
  
+  	^ stat ifNotNil: [ stat fileName ] ifNil: [  self splitToPathAndName: [ :path :n |  n ] ]
+ !
-  	^ self splitToPathAndName: [ :path :n |  n ].!

Item was added:
+ ----- Method: RioLocalFileSystem>>setRootString: (in category 'executive actions') -----
+ setRootString: aString  
+ 	rootString := aString.
+ 	 !

Item was added:
+ ----- Method: RioExecutive>>hashFor: (in category 'equality') -----
+ hashFor: aRio
+ 	
+ 	^ aRio value hash!

Item was added:
+ ----- Method: RioExecutive>>is:sameAs: (in category 'equality') -----
+ is: aRio sameAs: bRio
+ 
+ 	^ aRio value = bRio value!

Item was added:
+ ----- Method: RioExecutive>>arePathsCaseSensitive (in category 'case-sensitivity') -----
+ arePathsCaseSensitive
+ 
+ 	^ (self is: $a sameAs: $A) not
+ 	
+ !

Item was changed:
  ----- Method: RioLocalFileSystem>>initializeDefault (in category 'executive actions') -----
  initializeDefault
  
+ 	self setRootString: self pathDelimiter;
- 	self setRoot: self pathDelimiter;
  		setDefault: self getDefaultDirectory!

Item was changed:
  ----- Method: RioLocalDosFileSystem>>driveLetter (in category 'accessing') -----
  driveLetter
  
+ 	^ self rootString first!
- 	^ root first!

Item was added:
+ ----- Method: RioExecutive>>fullFor: (in category 'as yet unclassified') -----
+ fullFor: aRio
+ 
+ 	"the absolute path of this rio, or if relative 
+ 	combine with #defaultDirectory to obtain the full path"
+ 	
+ 	aRio value isEmpty ifTrue: [ ^ self defaultDirectory ].
+ 	
+ 	(self isFull: aRio) ifTrue: [ ^ aRio ].
+ 
+ 	^ aRio newFrom: (self defaultDirectory value, self pathDelimiter, aRio value)!

Item was added:
+ ----- Method: RioExecutive>>basicReader: (in category 'as yet unclassified') -----
+ basicReader: aRio
+ 
+ 	^ self class fileStreamClass new open: aRio forWrite: false!

Item was added:
+ ----- Method: RioExecutive>>touch: (in category 'as yet unclassified') -----
+ touch: aRio
+ 
+ 	aRio writer close!

Item was added:
+ ----- Method: RioExecutive>>root (in category 'as yet unclassified') -----
+ root
+ 
+ 	^ self makeNewRioOfClass: self rioClass fromString: self rootString!

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

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

Item was added:
+ ----- Method: RioExecutive>>rioClass (in category 'as yet unclassified') -----
+ rioClass
+ 
+ 	^ Smalltalk at: #Rio ifAbsent: [ RioKernel ]!

Item was added:
+ ----- Method: RioExecutive>>makeNewRioOfClass:fromString: (in category 'as yet unclassified') -----
+ makeNewRioOfClass: aRioClass fromString: aString
+ 
+ 	^ aRioClass executive: self value: aString !

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

Item was changed:
  ----- Method: RioKernel>>basicReader (in category 'public file') -----
  basicReader
   	
+ 	^ executive basicReader: self!
- 	^ self class fileStreamClass new open: self forWrite: false!

Item was added:
+ ----- Method: RioExecutive>>isFull: (in category 'as yet unclassified') -----
+ isFull: aRio
+ 
+ 	^ aRio value beginsWith: self rootString!

Item was added:
+ ----- Method: RioExecutive>>isRoot: (in category 'testing') -----
+ isRoot: aRioOrString
+ 
+ 	^ aRioOrString value = self rootString!

Item was added:
+ ----- Method: RioExecutive>>isDirectory: (in category 'as yet unclassified') -----
+ isDirectory: aRio 
+ 
+ 	^ aRio stat ifNil: [ false ] ifNotNil: [ aRio stat isDirectory ]
+ !

Item was added:
+ ----- Method: SocketStream>>copyTo:size:withProgress: (in category '*rio-kernel') -----
+ copyTo: out size: size withProgress: label 
+ 
+ 	| barPos read |
+  	
+ 	self isBinary ifTrue: [ out binary ].
+ 
+ 	label asString displayProgressAt: Sensor cursorPoint
+ 		from: (barPos := 0) to: size
+ 		during: [:bar |
+ 				[self atEnd] whileFalse:
+ 					[ 
+ 					  bar value: barPos.
+ 					  self receiveAvailableData.
+ 					  out nextPutAll: (read := self nextAllInBuffer).
+ 					  barPos := barPos + read size
+ 				  ].
+ 
+ 		].!

Item was added:
+ ----- Method: RioExecutive>>delete: (in category 'as yet unclassified') -----
+ delete: aRio
+ 
+ 	aRio isDirectory ifTrue: [ ^ aRio rmdir ].
+ 	self deleteFile: aRio.!

Item was changed:
  ----- Method: RioKernel class>>new: (in category 'as yet unclassified') -----
  new: aPathOrRio
  
  	"the preferred generic instanciation method, 
  	will call the correct specific instanciation method on the correct class"
  
  	aPathOrRio isRio ifTrue: [ ^ aPathOrRio copy ].
  	                                                                                                            
+ 	self allSubclassesDo: [ :c | (c canInstanciate: aPathOrRio) ifTrue: [ ^ c defaultExecutive makeNewRioOfClass: c fromString: aPathOrRio ]].              
- 	self allSubclassesDo: [ :c | (c canInstanciate: aPathOrRio) ifTrue: [ ^ self defaultExecutive makeNewRioOfClass: c fromString: aPathOrRio ]].              
  	
  	^ self defaultExecutive makeNewRioOfClass: self fromString: aPathOrRio!

Item was removed:
- ----- Method: RioLocalFileSystem>>pathDelimiterChar (in category 'executive actions') -----
- pathDelimiterChar
-  
- 	^ $/
- !

Item was removed:
- ----- Method: RioLocalFileSystem>>importValue: (in category 'executive actions') -----
- importValue: path
-  
- 	path isEmpty ifTrue: [  ^ '' ].
- 	
- 	(self isRoot: path) ifTrue: [ ^ root ].
- 	
-  	(path last = self pathDelimiter first) ifTrue: [ ^ path allButLast ].
- 	
- 	^path!

Item was removed:
- ----- Method: RioLocalFileSystem>>isFile: (in category 'rio support') -----
- isFile: aRio 
- 
- 	^ aRio stat ifNil: [ false ] ifNotNil: [ aRio stat isFile ]
- !

Item was removed:
- ----- Method: RioLocalFileSystem>>hashFor: (in category 'case-sensitivity') -----
- hashFor: aRio
- 	
- 	^ aRio value hash!

Item was removed:
- ----- Method: RioLocalFileSystem>>is:sameAs: (in category 'case-sensitivity') -----
- is: aRio sameAs: bRio
- 
- 	^ aRio value = bRio value!

Item was removed:
- ----- Method: RioLocalFileSystem>>arePathsCaseSensitive (in category 'case-sensitivity') -----
- arePathsCaseSensitive
- 
- 	^ (self is: $a sameAs: $A) not
- 	
- !

Item was removed:
- ----- Method: RioLocalFileSystem>>setRoot: (in category 'executive actions') -----
- setRoot: r  
- 	root := r.
- 	 !

Item was removed:
- ----- Method: RioLocalFileSystem>>fullFor: (in category 'rio support') -----
- fullFor: aRio
- 
- 	"the absolute path of this rio, or if relative 
- 	combine with #defaultDirectory to obtain the full path"
- 	
- 	aRio value isEmpty ifTrue: [ ^ self defaultDirectory ].
- 	
- 	(self isFull: aRio) ifTrue: [ ^ aRio ].
- 
- 	^ aRio newFrom: (self defaultDirectory value, self pathDelimiter, aRio value)!

Item was removed:
- ----- Method: RioLocalFileSystem>>root (in category 'executive actions') -----
- root
- 
- 	^ self makeNewRioOfClass: self rioClass fromString: root!

Item was removed:
- ----- Method: RioLocalFileSystem>>pathDelimiter (in category 'executive actions') -----
- pathDelimiter
-  
- 	^ '/'
- !

Item was removed:
- ----- Method: RioLocalFileSystem>>makeNewRioOfClass:fromString: (in category 'factory') -----
- makeNewRioOfClass: aRioClass fromString: aString
- 
- 	^ aRioClass executive: self value: aString !

Item was removed:
- ----- Method: RioLocalFileSystem>>rioClass (in category 'factory') -----
- rioClass
- 
- 	^ Smalltalk at: #Rio ifAbsent: [ RioKernel ]!

Item was removed:
- ----- Method: RioLocalFileSystem>>isFull: (in category 'rio support') -----
- isFull: aRio
- 
- 	^ aRio value beginsWith: root!

Item was removed:
- ----- Method: RioLocalFileSystem>>isRoot: (in category 'rio support') -----
- isRoot: aRioOrString
- 
- 	^ aRioOrString value = root!

Item was removed:
- ----- Method: RioKernel>>from: (in category 'as yet unclassified') -----
- from: aStringable
- 		
-  	 self value: aStringable!



More information about the Packages mailing list