ImageView.st
author Claus Gittinger <cg@exept.de>
Fri, 17 Nov 1995 18:23:36 +0100
changeset 89 eec056360d03
parent 86 4d7dbb5f1719
child 90 3c7a3015e178
permissions -rw-r--r--
*** empty log message ***

"
 COPYRIGHT (c) 1993 by Claus Gittinger
	      All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"

SimpleView subclass:#ImageView
	 instanceVariableNames:'image adjust'
	 classVariableNames:''
	 poolDictionaries:''
	 category:'Views-Misc'
!

!ImageView class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1993 by Claus Gittinger
	      All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"
!

documentation
"
    This View knows how to display an image (or form).

    You can display an image with:

	ImageView openOn:anImageFileName
    or:
	ImageView openOnImage:anImage
    or:
	ImageView new image:anImage

    i.e.

	ImageView openOn:'bitmaps/garfield.gif'
	ImageView openOn:'bitmaps/SBrowser.xbm'

	ImageView openOnImage:(Image fromFile:'bitmaps/garfield.gif')
	ImageView openOnImage:(Form fromFile:'SBrowser.xbm')
"
!

version
    ^ '$Header: /cvs/stx/stx/libwidg2/ImageView.st,v 1.17 1995-11-17 17:23:34 cg Exp $'
! !

!ImageView class methodsFor:'startup'!

openOn:aFileName
    "startup an image viewer on an image read from a file"

    |top img e|

    img := Image fromFile:aFileName.
    img isNil ifTrue:[
	aFileName asFilename exists ifTrue:[
	    e := 'unknown/unsupported image format'
	] ifFalse:[
	    e := 'no such image'.
	].
	self warn:e.
	^ nil
    ].
    top := self openOnImage:img.

    top label:aFileName.
    top iconLabel:aFileName asFilename baseName.

    ^ top

    "
     ImageView openOn:'bitmaps/garfield.gif'
     ImageView openOn:'/phys/porty/tmp/img.pcx'
    "
!

openOnImage:anImage
    "startup an image viewer on an image"

    |top v imageView icnW icnH iconView magX magY mag lbl|

    anImage isImage ifTrue:[
	lbl := 'an Image'
    ] ifFalse:[
	lbl := 'a Form'
    ].
    top := StandardSystemView label:lbl.

    v := HVScrollableView for:self in:top.
    v origin:0@0 extent:1.0@1.0. 
    imageView := v scrolledView.

    anImage notNil ifTrue:[
	imageView image:anImage.

	"define an icon view showing a little version of image.
	 Since some window managers cannot handle this correctly (twm),
	 this is only done when running on an IRIS"

	(true "(OperatingSystem getSystemType = 'iris')" 
	and:[StyleSheet name == #iris]) ifTrue:[
	    iconView := self new.

	    "for now; should somehow get access to preferred iconview extent ..."
	    icnW := 86.
	      icnH := 68.

	    ((anImage width <= icnW) and:[anImage height <= icnH]) ifTrue:[
		iconView extent:(anImage width @ anImage height).
		mag := 1 @ 1
	    ] ifFalse:[
		magX := icnW / anImage width.
		magY := icnH / anImage height.

		"scale image"
"
		mag := magX @ magY.
"
		"preserve ratio"
" 
		mag := (magX min:magY) asPoint.
" 
" "
		mag := (magX max:magY) asPoint.
" "

		iconView extent:((anImage width @ anImage height) * mag) rounded.
	    ].

	    top iconView:iconView.
	].
    ].

    top open.

    iconView notNil ifTrue:[
	top windowGroup addView:iconView.
	[ 
	    iconView image:(anImage magnifyBy:mag).
	] forkAt:4
    ].
    ^ top

    "
     ImageView openOnImage:(Image fromFile:'bitmaps/garfield.gif')
     ImageView openOnImage:(Image fromFile:'bitmaps/SBrowser.xbm')
     ImageView openOnImage:(Form fromFile:'bitmaps/SBrowser.xbm')
    "
! !

!ImageView methodsFor:'release'!

destroy
    image := nil.
    super destroy.
! !

!ImageView methodsFor:'drawing'!

redraw
    |clrMap x y|

    image notNil ifTrue:[
	image := image on:device.
	self clear.
	(image depth == 1) ifTrue:[
	    clrMap := image colorMap.
	    clrMap notNil ifTrue:[
		self paint:(clrMap at:2) on:(clrMap at:1).
	    ] ifFalse:[
		self paint:Color black on:Color white.
	    ]
	].
	layout == #center ifTrue:[
	    x := (width - (image extent x)) // 2.
	    y := (height - (image extent y)) // 2.
	] ifFalse:[
	    x := y := 0
	].
	self displayOpaqueForm:image x:x y:y 
    ]

    "Modified: 17.11.1995 / 15:44:14 / cg"
! !

!ImageView methodsFor:'accessing'!

image:anImage
    "set the image - show a wait cursor, since image dithering may take a while"

    image := anImage.
    anImage notNil ifTrue:[
	self cursor:Cursor wait.
	shown ifTrue:[
	    self redraw
	].
	self contentsChanged.
	self cursor:(Cursor normal).
    ].

    "
     ImageView new realize image:(Image fromFile:'bitmaps/claus.gif')

     |f|
     f := Image fromFile:'bitmaps/SBrowser.xbm'.
     f colorMap:(Array with:Color red with:Color yellow).
     ImageView new realize image:f
    "
!

image
    "return the image"

    ^ image
!

adjust:layoutSymbol
    "set the adjust (how the image is displayed);
     currently, only support #topLeft and #center"

    adjust := layoutSymbol
! !

!ImageView methodsFor:'queries'!

widthOfContents
    "return the images width - scrollbar needs this info"

    image isNil ifTrue:[^ 0].
    ^ image width
!

heightOfContents
    "return the images height - scrollbar needs this info"

    image isNil ifTrue:[^ 0].
    ^ image height
! !