[squeak-dev] The Trunk: Files-ar.87.mcz

commits at source.squeak.org commits at source.squeak.org
Sun Sep 5 17:57:42 UTC 2010


Andreas Raab uploaded a new version of Files to project The Trunk:
http://source.squeak.org/trunk/Files-ar.87.mcz

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

Name: Files-ar.87
Author: ar
Time: 5 September 2010, 10:57:31.132 am
UUID: 88d0ea93-b560-fe4c-bf50-b37a93c759fe
Ancestors: Files-ar.86

Restructurings to reduce package depencencies.

=============== Diff against Files-ar.86 ===============

Item was changed:
  ----- Method: FileStream class>>unload (in category 'class initialization') -----
  unload
  
+ 	FileServices unregisterFileReader: self !
- 	FileList unregisterFileReader: self !

Item was changed:
  ----- Method: DirectoryEntry>>services (in category 'services') -----
  services
  	"Answer the same collection of SimpleServiceEntry's accessed by the FileList."
+ 	^ FileServices itemsForFile: self fullName!
- 	^ FileList itemsForFile: self fullName!

Item was changed:
  ----- Method: FileStream class>>initialize (in category 'initialize-release') -----
  initialize
  
+ 	FileServices registerFileReader: self!
- 	FileList registerFileReader: self!

Item was removed:
- ----- Method: FileDirectory>>eToyUserListUrl: (in category 'school support') -----
- eToyUserListUrl: urlString
- 	^ServerDirectory eToyUserListUrlForFileDirectory: self put: urlString.!

Item was removed:
- ----- Method: FileDirectory>>eToyUserListUrl (in category 'school support') -----
- eToyUserListUrl
- 	^ServerDirectory eToyUserListUrlForFileDirectory: self!

Item was removed:
- ----- Method: FileDirectory>>eToyBaseFolderSpec (in category 'school support') -----
- eToyBaseFolderSpec
- 	^ServerDirectory eToyBaseFolderSpecForFileDirectory: self!

Item was removed:
- ----- Method: FileDirectory>>eToyBaseFolderSpec: (in category 'school support') -----
- eToyBaseFolderSpec: aString
- 	^ServerDirectory eToyBaseFolderSpecForFileDirectory: self put: aString!

Item was removed:
- ----- Method: FileStream class>>httpPostDocument:args: (in category 'browser requests') -----
- httpPostDocument: url args: argsDict
- 	| argString |
- 	argString := argsDict
- 		ifNotNil: [argString := HTTPSocket argString: argsDict]
- 		ifNil: [''].
- 	^self post: argString url: url , argString ifError: [self halt]!

Item was removed:
- ----- Method: FileStream class>>requestURL:target: (in category 'browser requests') -----
- requestURL: url target: target
- 	"FileStream requestURL:'http://isgwww.cs.uni-magdeburg.de/~raab' target: ':=blank' "
- 	^self concreteStream new requestURL: url target: target!

Item was removed:
- ----- Method: FileDirectory>>hasEToyUserList (in category 'school support') -----
- hasEToyUserList
- 	^self eToyUserListUrl notNil or:[self eToyBaseFolderSpec notNil]!

Item was removed:
- ----- Method: FileStream class>>post:target:url:ifError: (in category 'browser requests') -----
- post: data target: target url: url ifError: errorBlock
- 	^self concreteStream new post: data target: target url: url ifError: errorBlock!

Item was removed:
- ----- Method: FileStream>>fileIntoNewChangeSet (in category 'fileIn/Out') -----
- fileIntoNewChangeSet
- 	"File all of my contents into a new change set." 
- 
- 	self readOnly.
- 	ChangesOrganizer newChangesFromStream: self named: (self localName)
- !

Item was removed:
- ----- Method: StandardFileStream>>compressFile (in category 'read, write, position') -----
- compressFile
- 	"Write a new file that has the data in me compressed in GZip format."
- 	| zipped buffer |
- 
- 	self readOnly; binary.
- 	zipped := self directory newFileNamed: (self name, FileDirectory dot, 'gz').
- 	zipped binary; setFileTypeToObject.
- 		"Type and Creator not to be text, so can be enclosed in an email"
- 	zipped := GZipWriteStream on: zipped.
- 	buffer := ByteArray new: 50000.
- 	'Compressing ', self fullName displayProgressAt: Sensor cursorPoint
- 		from: 0 to: self size
- 		during: [:bar |
- 			[self atEnd] whileFalse: [
- 				bar value: self position.
- 				zipped nextPutAll: (self nextInto: buffer)].
- 			zipped close.
- 			self close].
- 	^zipped!

Item was removed:
- ----- Method: FileStream>>viewGZipContents (in category 'editing') -----
- viewGZipContents
- 	"View the contents of a gzipped file"
- 
- 	| stringContents |
- 	self binary.
- 	stringContents := self contentsOfEntireFile.
- 	stringContents := Cursor wait showWhile: [(GZipReadStream on: stringContents) upToEnd].
- 	stringContents := stringContents asString withSqueakLineEndings.
- 
- 	Workspace new
- 		contents: stringContents;
- 		openLabel: 'Decompressed contents of: ', self localName!

Item was removed:
- ----- Method: FileDirectory>>eToyUserName: (in category 'school support') -----
- eToyUserName: aString
- 	"Set the default directory from the given user name"
- 	| dirName |
- 	dirName := self eToyBaseFolderSpec. "something like 'U:\Squeak\users\*-Squeak'"
- 	dirName ifNil:[^self].
- 	dirName := dirName copyReplaceAll:'*' with: aString.
- "	dirName last = self class pathNameDelimiter ifFalse:[dirName := dirName, self slash].
- 	FileDirectory setDefaultDirectoryFrom: dirName.
- 	dirName := dirName copyFrom: 1 to: dirName size - 1.
- 
- "	pathName := FilePath pathName: dirName!

Item was removed:
- ----- Method: FileStream>>edit (in category 'editing') -----
- edit
- 	"Create and schedule an editor on this file."
- 
- 	FileList openEditorOn: self editString: nil.
- !

Item was removed:
- ----- Method: FileDirectory>>eToyUserList (in category 'school support') -----
- eToyUserList
- 	| spec index fd list match |
- 	spec := self eToyBaseFolderSpec. "something like 'U:\Squeak\users\*-Squeak'."
- 	spec ifNil:[^ServerDirectory eToyUserListForFileDirectory: self].
- 	"Compute list of users based on base folder spec"
- 	index := spec indexOf: $*. "we really need one"
- 	index = 0 ifTrue:[^ServerDirectory eToyUserListForFileDirectory: self].
- 	fd := FileDirectory on: (FileDirectory dirPathFor: (spec copyFrom: 1 to: index)).
- 	"reject all non-directories"
- 	list := fd entries select:[:each| each isDirectory].
- 	"reject all non-matching entries"
- 	match := spec copyFrom: fd pathName size + 2 to: spec size.
- 	list := list collect:[:each| each name].
- 	list := list select:[:each| match match: each].
- 	"extract the names (e.g., those positions that match '*')"
- 	index := match indexOf: $*.
- 	list := list collect:[:each|
- 		each copyFrom: index to: each size - (match size - index)].
- 	^list!

Item was removed:
- ----- Method: FileStream class>>post:url:ifError: (in category 'browser requests') -----
- post: data url: url ifError: errorBlock
- 	^self post: data target: nil url: url ifError: errorBlock!

Item was removed:
- ----- Method: FileStream class>>requestURLStream: (in category 'browser requests') -----
- requestURLStream: url
- 	"FileStream requestURLStream:'http://isgwww.cs.uni-magdeburg.de/~raab'"
- 	^self concreteStream new requestURLStream: url!

Item was removed:
- ----- Method: FileStream class>>requestURLStream:ifError: (in category 'browser requests') -----
- requestURLStream: url ifError: errorBlock
- 	"FileStream requestURLStream:'http://isgwww.cs.uni-magdeburg.de/~raab'"
- 	^self concreteStream new requestURLStream: url ifError: errorBlock!

Item was removed:
- ----- Method: FileDirectory class>>searchAllFilesForAString (in category 'name utilities') -----
- searchAllFilesForAString
- 
- 	"Prompt the user for a search string, and a starting directory. Search the contents of all files in the starting directory and its subdirectories for the search string (case-insensitive search.)
- 	List the paths of files in which it is found on the Transcript.
- 	By Stewart MacLean 5/00; subsequently moved to FileDirectory class-side, and refactored to call FileDirectory.filesContaining:caseSensitive:"
- 
- 	| searchString dir |
- 
- 	searchString := UIManager default request: 'Enter search string'.
- 	searchString isEmpty ifTrue: [^nil].
- 	Transcript cr; show: 'Searching for ', searchString printString, ' ...'.
- 	(dir := PluggableFileList getFolderDialog open) ifNotNil:
- 		[(dir filesContaining: searchString caseSensitive: false) do:
- 				[:pathname | Transcript cr; show: pathname]].
- 	Transcript cr; show: 'Finished searching for ', searchString printString
- 
- 	"FileDirectory searchAllFilesForAString"!

Item was removed:
- ----- Method: FileStream class>>httpPostMultipart:args: (in category 'browser requests') -----
- httpPostMultipart: url args: argsDict
- 	| mimeBorder argsStream crLf resultStream result |
- 	" do multipart/form-data encoding rather than x-www-urlencoded "
- 
- 	crLf := String crlf.
- 	mimeBorder := '----squeak-', Time millisecondClockValue printString, '-stuff-----'.
- 	"encode the arguments dictionary"
- 	argsStream := WriteStream on: String new.
- 	argsDict associationsDo: [:assoc |
- 		assoc value do: [ :value | | fieldValue |
- 		"print the boundary"
- 		argsStream nextPutAll: '--', mimeBorder, crLf.
- 		" check if it's a non-text field "
- 		argsStream nextPutAll: 'Content-disposition: form-data; name="', assoc key, '"'.
- 		(value isKindOf: MIMEDocument)
- 			ifFalse: [fieldValue := value]
- 			ifTrue: [argsStream nextPutAll: ' filename="', value url pathForFile, '"', crLf, 'Content-Type: ', value contentType.
- 				fieldValue := (value content
- 					ifNil: [(FileStream fileNamed: value url pathForFile) contentsOfEntireFile]
- 					ifNotNil: [value content]) asString].
- " Transcript show: 'field=', key, '; value=', fieldValue; cr. "
- 		argsStream nextPutAll: crLf, crLf, fieldValue, crLf.
- 	]].
- 	argsStream nextPutAll: '--', mimeBorder, '--'.
- 
- 	resultStream := self
- 		post: 
- 			('Content-type: multipart/form-data; boundary=', mimeBorder, crLf,
- 			'Content-length: ', argsStream contents size printString, crLf, crLf, 
- 			argsStream contents)
- 		url: url ifError: [^'Error in post ' url asString].
- 	"get the header of the reply"
- 	result := resultStream upToEnd.
- 	^MIMEDocument content: result!




More information about the Squeak-dev mailing list