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

squeak-dev-noreply at lists.squeakfoundation.org squeak-dev-noreply at lists.squeakfoundation.org
Sat Feb 28 13:31:16 UTC 2009


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

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

Name: File-Base-kph.17
Author: kph
Time: 28 February 2009, 1:31:10 pm
UUID: 0fe2d2dd-059c-11de-9b6f-000a95edb42a
Ancestors: File-Base-kph.16

All non-archive tests pass

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

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

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

Item was added:
+ ----- Method: Directory>>isOverwriting (in category 'directory/container actions') -----
+ isOverwriting
+ 
+ 	^ overwriting ifNil: [ false ]!

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

Item was added:
+ ----- Method: FileArchive>>expandTo:cachingIn: (in category 'public') -----
+ expandTo: destDir cachingIn: cacheDir
+ 
+ 	"expand a zip file into a local directory, if remote there may be a cached version in the cacheDir
+ 	this is not a perfect implementation of the rio API, but bob needed it, so it may be useful to others"
+ 
+ 	"a better api
+ 	
+ 	(cacheDir addIfAbsent: aZip) expandTo: destDir.
+ 	
+ 	"
+ 			
+ 	| localZipFile zipFile |
+ 	
+ 	zipFile := executive file.
+ 	
+ 	zipFile executive isRemote 
+ 		ifTrue: [ 
+ 		
+ 			localZipFile := cacheDir  /  zipFile fileName.
+ 				
+ 			localZipFile exists ifFalse: [ 
+ 				self log info downloading: zipFile.
+ 				localZipFile parent mkpath add: zipFile ].	
+ 		]
+ 		ifFalse: [ localZipFile := zipFile ].
+ 		
+ 	self log info bob expanding: localZipFile to: destDir.	
+ 
+ 	self exec: 'unzip ', localZipFile, ' -d ', destDir full mkpath.
+ 	
+ 	^ localZipFile
+ 
+ 	!

Item was changed:
  ----- Method: Directory>>addAll:relativeTo: (in category 'directory/container actions') -----
  addAll: someFD relativeTo: aBaseDir
  	
  	"someFd must all have the same executor"
  	
  	"we could perform a sort here to handle the other case"
  	
  	someFD isEmpty ifTrue: [ ^ #() ].
  	
+ 	^ [ someFD first executive addAll: someFD relativeTo: aBaseDir toDir: self ] 
+ 		on: FileNotification do: [ :ex | ex isOverwrite: self isOverwriting]!
- 	^ someFD first executive addAll: someFD relativeTo: aBaseDir toDir: self.!

Item was changed:
  ----- Method: FileFtpExecutive>>toDirLocal:addAllRemote:relativeTo: (in category 'local/remote file copy') -----
  toDirLocal: aDir addAllRemote: someFD relativeTo: aBaseDir
  
+ 	^ self 
+ 		copyUsing:  #copyRemoteFile:toLocalFile: 
+ 		from: aDir 
+ 		to: someFD 
+ 		relativeTo: aBaseDir
+  !
- 	^ self toDirRemote: aDir addAllLocal: someFD relativeTo: aBaseDir 
- 		copySelector: #copyRemoteFile:toLocalFile:!

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

Item was changed:
  File subclass: #Directory
+ 	instanceVariableNames: 'overwriting'
- 	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!

Item was added:
+ ----- Method: Directory>>beOverwriting (in category 'directory/container actions') -----
+ beOverwriting
+ 
+ 	overwriting := true!

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

Item was changed:
  ----- Method: FileFtpExecutive>>copyRemoteFile:toRemoteFile: (in category 'external ftp') -----
+ copyRemoteFile: aFile toRemoteFile: bFile  
- copyRemoteFile: aFile toRemoteFile: bFile
  
  	"we copy the executives to enable multi threaded copying and because we cant read and write with the same executive"
  	
  	^ (aFile executive: aFile executive copy initialize) copyTo: (bFile executive: bFile executive copy initialize)!

Item was changed:
  ----- Method: FileFtpExecutive>>toDirRemote:addAllLocal:relativeTo: (in category 'local/remote file copy') -----
  toDirRemote: aDir addAllLocal: someFD relativeTo: aBaseDir
  
+ 	^ self 
+ 		copyUsing:  #copyLocalFile:toRemoteFile:
+ 		from: aDir 
+ 		to: someFD 
+ 		relativeTo: aBaseDir
+  !
- 	^ self toDirRemote: aDir addAllLocal: someFD relativeTo: aBaseDir 
- 		copySelector: #copyLocalFile:toRemoteFile:!

Item was changed:
  ----- Method: Directory>>add: (in category 'directory/container actions') -----
  add: aFD
  		 
+ 	^ self addAll: (Array with: aFD)	 
- 	^ (self addAll: (Array with: aFD)	) first
  		
  "
  	self assert: (('a' asDirectory mkpath add: 'b' asFile touch)  = 'a/b' asFile)
  "!

Item was changed:
  ----- Method: FileFtpExecutive>>toDirRemote:addAllRemote:relativeTo: (in category 'local/remote file copy') -----
  toDirRemote: aDir addAllRemote: someFD relativeTo: aBaseDir
  
+ 	^ self 
+ 		copyUsing:  #copyRemoteFile:toRemoteFile:  
+ 		from: aDir 
+ 		to: someFD 
+ 		relativeTo: aBaseDir
+  !
- 	^ self toDirRemote: aDir addAllLocal: someFD relativeTo: aBaseDir 
- 		 copySelector: #copyRemoteFile:toRemoteFile:!

Item was changed:
  ----- Method: Directory>>addTree: (in category 'directory/container actions') -----
  addTree: aDir
  	"this adds  all the contents of aDir to the directory, not aDir itself"
  	
  	| list |
  	self validateIsContainer.
   	
  	list := aDir isCollection ifTrue: [ aDir ] ifFalse: [ Array with: aDir ].
  		
  	list do: [ :ea | 
  		
+ 		self addAll: ((ea all entries) addFirst: ea; yourself) relativeTo: ea parent.
- 		self addAll: (ea all entries; addFirst: ea; yourself) relativeTo: ea parent.
  	
  	].
  	
   !

Item was added:
+ ----- Method: Directory>>overwrite (in category 'directory/container actions') -----
+ overwrite
+ 
+ 	^ self copy beOverwriting!

Item was changed:
  ----- Method: File>>resolveMatchAll (in category 'enumeration') -----
  resolveMatchAll
  
+ 	^ self parent filesMatching: self fileName!
- 	^ self parent filesMatching: self filename!

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

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



More information about the Packages mailing list