[Seaside] [FIX] large files / WAFile & MultipartChunk & WAKom streaming

Colin Curtin alpine at umail.ucsb.edu
Thu Apr 8 13:31:53 CEST 2004


Abstract: Changeset included starts a base for low-er memory overhead 
for serving files, and a WAFile that caches files as it receives them.

A while ago I was complaining about how #anchorWithDocument: didn't work 
too well with large files; additionally I saw Michal's email about 
WAFile and caching to disk.

My changeset includes a WAStreamedDocumentHandler to be called by 
#urlForStreamedDocument:mimeType:filename for filestreams to be directly 
attached to the response stream. This (should) result in a lower memory 
overhead for serving files. It's not quite right yet - the contents are 
still copied to memory for the WAGenericResponse. But the jist of it 
seems OK. ;)

Time trials: -download measured with Mozilla-
size | stock | modified
30k:      1.00up 3.00down    -->    1.30up 4.00down
150k:    1.27up 4.00down    -->    1.26up 4.00down
2500k:  1:49.05up 5.00down  -->  28.20up 10.00down
13300k: gave up (20min)      -->    3:17up 16.00down (after a long pause)

Those trials would be more useful if I could check the memory use. Is 
there an easy way to do this?

Conclusion: My document handler would show significant improvement if 
Comanche worked (almost) exclusively in streams. As it stands now, it's 
just a base for things to come.

Also included is WAFile, initialized with a fileName and stream, which 
will cache to a temp file, hopefully furthering the solution Michal 
created in his changesets.

Problems:

- WAFile can clutter up your temp directory if you don't call WAFile's 
clearTemp. There must be a better way of doing this. (My ensure: block 
in WAStreamedUploadTest doesn't work...why?)

- The streamed document class may deal with just streams, true, but the 
response gets sent all the way up to HttpAdaptor>>#writeResponse:for:, 
and to actually stream things from disk properly would take a bit of 
working (as was previously said).


Good? Bad?


Colin
-------------- next part --------------
'From Squeak3.6 of ''6 October 2003'' [latest update: #5429] on 8 April 2004 at 3:08:33 am'!
Object subclass: #WAFile
	instanceVariableNames: 'contents fileName tempFile '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Seaside/Base-Utilities'!
TestCase subclass: #WAFileTest
	instanceVariableNames: 'file localfilestream filename '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Seaside/Base-Utilities'!
WADocumentHandler subclass: #WAStreamedDocumentHandler
	instanceVariableNames: 'stream '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Seaside/Base-Handlers'!
WAComponent subclass: #WAStreamedUploadTest
	instanceVariableNames: 'file '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Seaside/Examples-Test'!

!WAFile methodsFor: 'as yet unclassified' stamp: 'cc 4/7/2004 18:33'!
clearTemp
	self tempDir deleteFileNamed: self tempFile! !

!WAFile methodsFor: 'as yet unclassified' stamp: 'cc 4/7/2004 15:55'!
contents
	^ self stream contents! !

!WAFile methodsFor: 'as yet unclassified' stamp: 'cc 4/7/2004 18:32'!
stream 
	^ self tempDir readOnlyFileNamed: self tempFile! !

!WAFile methodsFor: 'as yet unclassified' stamp: 'cc 4/7/2004 18:00'!
tempDir
	| default tempName |
	default _ FileDirectory default.
	tempName _ 'seaside-tmp'.

	(default directoryExists: tempName) ifFalse: [ default createDirectory: tempName ].

	^ default directoryNamed: tempName! !

!WAFile methodsFor: 'as yet unclassified' stamp: 'cc 4/7/2004 17:37'!
tempFile
	^ tempFile! !

!WAFile methodsFor: 'as yet unclassified' stamp: 'cc 4/7/2004 17:37'!
tempFile: aFileDirectory
	tempFile _ aFileDirectory! !


!WAFile class methodsFor: 'as yet unclassified' stamp: 'cc 4/7/2004 18:04'!
fileName: aName stream: aStream
	| tmpfilename newfile |
	tmpfilename _ UUID new asString.
	newfile _ self new.
	
	newfile tempDir putFile: aStream named: tmpfilename.
	^ newfile tempFile: tmpfilename; fileName: aName.! !


!WAFileTest methodsFor: 'as yet unclassified' stamp: 'cc 4/7/2004 18:20'!
setUp
	| ws |
	filename _ 'testing'.

	ws _ FileDirectory default forceNewFileNamed: filename.
	ws nextPutAll: 'this is a test'.
	ws close.

	localfilestream _ FileDirectory default fileNamed: filename.

	file _ WAFile fileName: filename stream: localfilestream.! !

!WAFileTest methodsFor: 'as yet unclassified' stamp: 'cc 4/7/2004 18:06'!
tearDown
	localfilestream close.
	FileDirectory default deleteFileNamed: filename.
	file _ nil.! !

!WAFileTest methodsFor: 'as yet unclassified' stamp: 'cc 4/7/2004 17:53'!
testContent
	self assert: file contents = 'this is a test'! !

!WAFileTest methodsFor: 'as yet unclassified' stamp: 'cc 4/7/2004 17:54'!
testFilename
	self assert: file fileName = filename! !


!WAHtmlRenderer methodsFor: 'documents' stamp: 'cc 4/7/2004 17:18'!
anchorWithStreamedDocument: aStream mimeType: mimeType fileName: fileName text: aString
	self openAnchorWithStreamedDocument: aStream mimeType: mimeType fileName: fileName.
	self text: aString.
	self close.! !

!WAHtmlRenderer methodsFor: 'documents' stamp: 'cc 4/7/2004 17:18'!
openAnchorWithStreamedDocument: aStream mimeType: mimeType fileName: fileName
	self attributeAt: 'href' put: (self urlForStreamedDocument: aStream mimeType: mimeType fileName: fileName).
	self openTag: #a.! !

!WAHtmlRenderer methodsFor: 'documents' stamp: 'cc 4/7/2004 17:14'!
urlForStreamedDocument: aStream mimeType: mimeType fileName: fileName
	^ WASession currentSession application urlForRequestHandler:
		(WAStreamedDocumentHandler
			stream: aStream
			mimeType: mimeType
			fileName: fileName)! !


!WAKom methodsFor: 'as yet unclassified' stamp: 'cc 4/7/2004 19:21'!
processMultipartFields: aRequest
	aRequest multipartFormFieldsDo:
		[:chunk |
		chunk fileName isEmptyOrNil ifFalse:
			[| file |
			file _ WAFile fileName: chunk fileName stream: chunk fileContents readStream.
			aRequest postFields at: chunk fieldName put: file]].! !


!WAStreamedDocumentHandler methodsFor: 'as yet unclassified' stamp: 'cc 4/7/2004 19:32'!
= other
	^ (other species = self species
		and: [other stream asString = self stream asString])
		and: [other mimeType = self mimeType]! !

!WAStreamedDocumentHandler methodsFor: 'as yet unclassified' stamp: 'cc 4/7/2004 17:12'!
document
	^ self shouldNotImplement! !

!WAStreamedDocumentHandler methodsFor: 'as yet unclassified' stamp: 'cc 4/7/2004 19:31'!
hash
	^ self stream hash bitXor: self mimeType hash! !

!WAStreamedDocumentHandler methodsFor: 'as yet unclassified' stamp: 'cc 4/7/2004 19:27'!
initializeWithStream: aStream mimeType: mimeString fileName: fileString
	stream _ aStream.
	mimeType _ mimeString.
	fileName _ fileString.! !

!WAStreamedDocumentHandler methodsFor: 'as yet unclassified' stamp: 'cc 4/8/2004 03:08'!
response
	| response buffer |
	response _ WAGenericResponse new.

	buffer _ String new: 50000.
	[self stream atEnd] whileFalse:
		[response nextPutAll: (self stream nextInto: buffer)].
	self stream close.

	response contentType: mimeType.
	response headerAt: 'Expires' put: 'Thu, 01 Jan 2095 12:00:00 GMT'.
	fileName ifNotNil: 
		[response headerAt: 'Content-Disposition' put: 'attachment; filename=' , fileName].
	^ response! !

!WAStreamedDocumentHandler methodsFor: 'as yet unclassified' stamp: 'cc 4/7/2004 17:05'!
stream
	^ stream! !

!WAStreamedDocumentHandler methodsFor: 'as yet unclassified' stamp: 'cc 4/7/2004 17:05'!
stream: aStream
	stream _ aStream! !


!WAStreamedDocumentHandler class methodsFor: 'as yet unclassified' stamp: 'cc 4/7/2004 19:29'!
stream: aStream mimeType: mimeString fileName: fileString
	^ self basicNew initializeWithStream: aStream mimeType: mimeString fileName: fileString! !


!WAStreamedUploadTest methodsFor: 'as yet unclassified' stamp: 'cc 4/7/2004 18:35'!
renderContentOn: html
	html heading: 'Upload Streamed File (for large files)'.
	
	html attributeAt: 'enctype' put: 'multipart/form-data'.
	html form: [
		html fileUploadWithCallback: [:f | file _ f].
		html submitButton.
	].

	file ifNotNil: [
		[html anchorWithStreamedDocument: file stream mimeType: 'application/octet-stream' fileName: file fileName text: file fileName]
			ensure: [file clearTemp]].! !

WAFileTest removeSelector: #contentTest!
WAFileTest removeSelector: #filenameTest!
WAFileTest removeSelector: #streamTest!
WAFile class removeSelector: #tempDir!
WAFile removeSelector: #contents:!
WAFile removeSelector: #stream:!


More information about the Seaside mailing list