[Seaside] How-to upload and view image ?

Wai Lun Mang mangwl at yahoo.com
Sun Sep 19 03:48:30 CEST 2004


I agree with you that I was a little disappointed with
the complicated procedure.  I am new to seaside so I
am also interested in this area, actually to alot of
areas to understand what seaside can really do and
what is missing from seaside to build complicated web
applications.

Anyway, after exploring a little, I think I found a
slightly easier way of doing this.

To save the uploaded image file:
	html form: [
		html fileUploadWithCallback: [:f |
			stream := FileStream newFileNamed: 'abc.jpg'.
			stream nextPutAll: f contents.
			stream close.
		].
		html submitButton.
	].

To display the uploaded saved image file:

	imageSize := ImageReadWriter imageSizeFromFileNamed:
'abc.jpg'.
	stream := FileStream oldFileNamed: 'abc.jpg'.
	html
		image: (html context urlForDocument: stream
contentsOfEntireFile mimeType: 'image/jpeg')
		width: imageSize x//4  "a quarter of the original
size"
		height: imageSize y//4.
	stream close.
	
And I have enclosed the changeset which contains the
changes I added for the #imageSize method.  Note that
the above example assumes jpeg files but the changes I
make should work for all the different kind of image
files supported in Squeak but I have tested them
because I don't have all the different kind of image
files.  I have only tested jpeg.

I hope this helps.

Mang :-)

--- Hilaire Fernandes <hilaire at ext.cri74.org> wrote:

> Thanks a lot for the tips! 
> 
> To which Squeak objet match the content in the
> WAFile? The inspector
> says it is a string. Is there any possibility to
> convert it to another
> format to retrieve information concerning the
> picture.
> 
> I have to admit that I am a bit disapointed
> regarding the over complicated
> procedure to just upload a simple picture. Not to
> say that Mime type
> and width and height still  need to be calculated
> from somewhere.
> 
> Regards,
> 
> Hilaire
> 
> On Sat, 11 Sep 2004 14:49:53 +0200
> Andreas Nilsson <wahboh at mac.com> wrote:
> 
>   > I just went through this so I'll try to explain
> what I did to get it 
>   > working:
>   > 
>   > First the upload form:
>   > html attributeAt: 'enctype' put:
> 'multipart/form-data'.
>   > html form: [	
>   > 	html fileUploadWithCallback: [:file | picture
> := file contents ].
>   > 	html submitButton.
>   > ].
>   > You get a WAFile in the block parameter so you
> can look in that class 
>   > for ideas, among other things it contains the
> content type.
>   > 
>   > Then to display the picture you have to wrap it
> in a class that 
>   > responds to #height, #width, #asMIMEDocument and
> returns unique values 
>   > in #= and #hash for different pictures
> (otherwise the images will be 
>   > cached, ie. they will not change when you change
> the contents of your 
>   > wrapper instance). #height and #width are just
> used for displaying so 
>   > they don't have to match the pictures
> properties, but it will strech / 
>   > shrink if they don't.
>   > I implemented asMIMEDocument in the following
> way in my wrapper class 
>   > (APicture):
>   > 
>   > #asMimeDocument
>   > 	^ MIMEDocument contentType: 'image/jpeg'
> content: contents.
>   > 
>   > Where contents is the contents from the form
> above that I passed to the 
>   > wrapper instance when I created it.
>   > 
>   > Then to display it you just pass an instance of
> your wrapper class 
>   > (APicture) to html's #imageWithForm method:
>   > 
>   > html imageWithForm: picture
>   > 
>   > Hope that helps!
>   > 
>   > /Adde
>   > 
>   > On 2004-09-11, at 14.28, Hilaire Fernandes
> wrote:
>   > 
>   > > Hello,
>   > >
>   > > I am a total newbie both to Seaside and Squeak
> (and more generaly to 
>   > > Smalltalk).
>   > >
>   > > I try to figure out how an user can upload an
> image into Seaside, then
>   > > how to use it in web page rendering.
>   > >
>   > > A code example to understand that will be more
> than enought.
>   > >
>   > > I saw the WAUploadTest class but I miss the
> second part where you want 
>   > > to use
>   > > the uploaded image to render the image in a
> web document.
>   > >
>   > > Thanks
>   > >
>   > > Hilaire
>   > >
> _______________________________________________
>   > > Seaside mailing list
>   > > Seaside at lists.squeakfoundation.org
>   > >
> http://lists.squeakfoundation.org/listinfo/seaside
>   > 
>   > _______________________________________________
>   > Seaside mailing list
>   > Seaside at lists.squeakfoundation.org
>   >
> http://lists.squeakfoundation.org/listinfo/seaside
>   > 
> _______________________________________________
> Seaside mailing list
> Seaside at lists.squeakfoundation.org
> http://lists.squeakfoundation.org/listinfo/seaside
> 
-------------- next part --------------
'From Squeak3.7beta of ''1 April 2004'' [latest update: #5948] on 18 September 2004 at 6:35:24 pm'!

!ImageReadWriter methodsFor: 'accessing' stamp: 'mang 9/14/2004 07:56'!
imageSize
	"Dencoding an image on stream and answer the image size."

	^self subclassResponsibility! !


!BMPReadWriter methodsFor: 'reading' stamp: 'mang 9/14/2004 08:08'!
imageSize
	stream binary.
	^self readImageSizeFromHeader.
! !

!BMPReadWriter methodsFor: 'reading' stamp: 'mang 9/14/2004 08:07'!
readImageSizeFromHeader
	| reserved |
	bfType _ stream nextLittleEndianNumber: 2.
	bfSize _ stream nextLittleEndianNumber: 4.
	reserved _ stream nextLittleEndianNumber: 4.
	bfOffBits _ stream nextLittleEndianNumber: 4.
	biSize _ stream nextLittleEndianNumber: 4.
	biWidth _ stream nextLittleEndianNumber: 4.
	biHeight _ stream nextLittleEndianNumber: 4.
	^biWidth at biHeight! !


!GIFReadWriter methodsFor: 'accessing' stamp: 'mang 9/14/2004 08:01'!
imageSize
	"Read in the next GIF image from the stream. Read it all into
memory first for speed."

	| imageSize |
	stream class == ReadWriteStream ifFalse: [
		stream binary.
		self on: (ReadWriteStream with: (stream contentsOfEntireFile))].

	self readHeader.
	imageSize _ self imageSizeFromBody.
	self close.
	^ imageSize
! !

!GIFReadWriter methodsFor: 'private-decoding' stamp: 'mang 9/14/2004 08:03'!
imageSizeFromBody
	"Read the GIF blocks. Modified to return a form.  "

	| imageSize extype block blocksize packedFields delay1 |
	imageSize _ nil.
	[stream atEnd] whileFalse: [
		block _ self next.
		block = Terminator ifTrue: [^ imageSize].
		block = ImageSeparator ifTrue: [
			imageSize isNil
				ifTrue: [^self readImageSizeFromBitData]
				ifFalse: [self skipBitData].
		] ifFalse: [
			block = Extension
				ifFalse: [^ imageSize "^ self error: 'Unknown block type'"].
			"Extension block"
			extype _ self next.	"extension type"
			extype = 16rF9 ifTrue: [  "graphics control"
				self next = 4 ifFalse: [^ imageSize "^ self error: 'corrupt GIF file'"].
				"====
				Reserved                      3 Bits
				Disposal Method               3 Bits
				User Input Flag               1 Bit
				Transparent Color Flag        1 Bit
				==="
 
				packedFields _ self next.
				delay1 := self next.	"delay time 1"
				delay := (self next*256 + delay1) *10.	 "delay time 2"
				transparentIndex _ self next.
				(packedFields bitAnd: 1) = 0 ifTrue: [transparentIndex _ nil].
				self next = 0 ifFalse: [^ imageSize "^ self error: 'corrupt GIF file'"].
			] ifFalse: [
				"Skip blocks"
				[(blocksize _ self next) > 0]
					whileTrue: [
						"Read the block and ignore it and eat the block terminator"
						self next: blocksize]]]]! !

!GIFReadWriter methodsFor: 'private-decoding' stamp: 'mang 9/14/2004 08:05'!
readImageSizeFromBitData
	"using modified Lempel-Ziv Welch algorithm."

	offset := self readWord at self readWord. "Image Left at Image Top"
	width _ self readWord.
	height _ self readWord.
	^width at height! !


!ImageReadWriter class methodsFor: 'image reading/writing' stamp: 'mang 9/14/2004 07:53'!
imageSizeFromFileNamed: fileName
	"Answer the image size stored on the file with the given name."
	| stream |
	stream _ FileStream readOnlyFileNamed: fileName.
	^self imageSizeFromStream: stream! !

!ImageReadWriter class methodsFor: 'image reading/writing' stamp: 'mang 9/14/2004 07:55'!
imageSizeFromStream: aBinaryStream
	"Answer the image size stored on the given stream.  closes the stream"
	| reader readerClass imageSize  |

	readerClass _ self withAllSubclasses
		detect: [:subclass | subclass understandsImageFormat: aBinaryStream]
		ifNone: [
			aBinaryStream close.
			^self error: 'image format not recognized'].
	reader _ readerClass new on: aBinaryStream reset.
	Cursor read showWhile: [
		imageSize _ reader imageSize.
		reader close].
	^ imageSize
! !


!JPEGReadWriter methodsFor: 'public access' stamp: 'mang 9/14/2004 08:20'!
imageSize

	^ self imageSizeDitheredToDepth: Display depth
! !

!JPEGReadWriter methodsFor: 'public access' stamp: 'mang 9/14/2004 08:21'!
imageSizeDitheredToDepth: depth

	ditherMask _ DitherMasks
		at: depth
		ifAbsent: [self error: 'can only dither to display depths'].
	residuals _ WordArray new: 3.
	sosSeen _ false.
	self parseFirstMarker.
	[sosSeen] whileFalse: [self parseNextMarker].
	^width @ height! !


!JPEGReadWriter2 methodsFor: 'public access' stamp: 'mang 9/14/2004 07:56'!
imageSize
	"Decode and answer a Form from my stream."

	^ self imageSizeSuggestedDepth: Display depth
! !

!JPEGReadWriter2 methodsFor: 'public access' stamp: 'mang 9/14/2004 07:59'!
imageSizeSuggestedDepth: depth
	"Decode and answer a Form of the given depth from my stream. Close the stream if it is a file stream. Possible depths are 16-bit and 32-bit."

	| bytes |
	bytes _ stream upToEnd.
	stream close.
	^self imageExtent: bytes
! !


!PCXReadWriter methodsFor: 'accessing' stamp: 'mang 9/14/2004 08:13'!
imageSize
	"Read in the next PCX image from the stream."

	^self readImageSizeFromHeader.
! !

!PCXReadWriter methodsFor: 'private-decoding' stamp: 'mang 9/14/2004 08:13'!
readImageSizeFromHeader

	| xMin xMax yMin yMax |
	self next.	"skip over manufacturer field"
	version _ self next.
	encoding _ self next.
	bitsPerPixel _ self next.
	xMin _ self nextWord.
	yMin _ self nextWord.
	xMax _ self nextWord.
	yMax _ self nextWord.
	width _ xMax - xMin + 1.
	height _ yMax - yMin + 1.
	^width at height



! !


!PNGReadWriter methodsFor: 'accessing' stamp: 'mang 9/14/2004 08:16'!
imageSize
	bigEndian := Smalltalk isBigEndian.
	filtersSeen _ Bag new.
	globalDataChunk _ nil.
	transparentPixelValue _ nil.
	unknownChunks _ Set new.
	stream reset.
	stream binary.
	stream skip: 8.
	[stream atEnd or: [width notNil and: [ height notNil]]] whileFalse: [self processNextChunk].
	^width at height! !



!XBMReadWriter methodsFor: 'private' stamp: 'mang 9/14/2004 08:19'!
readImageSizeFromHeader
	"Set width and height, and position stream at start of bytes"
	| number setwidth setheight fieldName |
	setwidth _ setheight _ false.
		[((stream atEnd) or: [setwidth and: [setheight]])]
		whileFalse: [
	  	self skipCComments.
		(stream nextMatchAll: '#define ') ifFalse: [^ false].
		(stream skipTo: $_) ifFalse: [^ false].
		fieldName _ String streamContents:
			[:source |
			[(stream atEnd) or: [ stream peek isSeparator ]]
				whileFalse: [ source nextPut: stream next]].
	  	(fieldName = 'width') ifTrue: [
			stream skipSeparators.
			number _ Integer readFrom: stream.
			(number > 0) ifTrue: [setwidth _true].
	  		width _ number.].
		(fieldName = 'height') ifTrue: [
			stream skipSeparators.
			number _ Integer readFrom: stream.
			(number > 0) ifTrue: [setheight _ true].
			height _ number.
			].
		].
	(setwidth & setheight) ifFalse: [^ nil].
	^width at height
! !

!XBMReadWriter methodsFor: 'accessing' stamp: 'mang 9/14/2004 08:17'!
imageSize
	"Read in the next xbm image from the stream."
	stream reset.
	stream ascii.
	^self readImageSizeFromHeader.
! !



More information about the Seaside mailing list