ImageView.st
author Claus Gittinger <cg@exept.de>
Tue, 10 Dec 2002 11:46:23 +0100
changeset 2402 4425948481b4
parent 2375 e0c7852263e4
child 2404 2b7591c982ac
permissions -rw-r--r--
category change

"
 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.
"

"{ Package: 'stx:libwidg2' }"

View subclass:#ImageView
	instanceVariableNames:'image magnifiedImage adjust imageChannel tileMode tileOffset'
	classVariableNames:'DoNotMagnifyQuery'
	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/gifImages/garfield.gif'
        ImageView openOn:'bitmaps/SBrowser.xbm'

        ImageView openOnImage:(Image fromFile:'bitmaps/gifImages/garfield.gif')
        ImageView openOnImage:(Image fromFile:'bitmaps/SBrowser.xbm')

    adjust:     
        controls how images are displayed;
        can be one of:
            #topLeft    - image is displayed as usual
            #center     - image is shown centered
            #fitBig     - big images are shrunk to make it fit the view
            #fitSmall   - small images are magnified to make it fit the view,
            #fit        - all images are magnified to fit the view

    [author:]
        Claus Gittinger

    [see also:]
        Image Form
"
! !

!ImageView class methodsFor:'initialization'!

initialize
    DoNotMagnifyQuery := QuerySignal new defaultAnswer:false.
! !

!ImageView class methodsFor:'queries - plugin'!

aspectSelectors
    ^ #( imageChannel )

    "Created: / 11.2.2000 / 00:37:33 / cg"
! !

!ImageView class methodsFor:'startup'!

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

    |fn imageView img e|

    fn := aFileName asFilename.

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

    imageView topView label:fn pathName iconLabel:(fn baseName).

    ^ imageView

    "
     ImageView openOn:'bitmaps/gifImages/garfield.gif'
     ImageView openOn:'bitmaps/xpmBitmaps/BOOK.xpm'
    "

    "Modified: / 31.10.1997 / 16:17:52 / cg"
!

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

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

    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 := ImageView new.

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

            imgWidth := anImage width.
            imgHeight := anImage height.

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

                "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 magnifiedBy:mag).
        ] forkAt:4
    ].
    ^ imageView

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

    "Modified: / 18.12.1997 / 11:46:19 / cg"
! !

!ImageView methodsFor:'accessing'!

adjust:layoutSymbol
    "set the adjust (how the image is displayed);
     currently, only support #topLeft, #center, #fitBig, #fitSmall and #fit:
            #topLeft    - image is displayed as usual
            #center     - image is shown centered
            #fitBig     - big images are shrunk to make it fit the view
            #fitSmall   - small images are magnified to make it fit the view,
            #fit        - all images are magnified to fit the view
    "

    adjust ~= layoutSymbol ifTrue:[
        adjust := layoutSymbol.

        magnifiedImage := nil.
        self shown ifTrue:[
            image notNil ifTrue:[
                self generateMagnifiedImage.
                self clear.
                self scrollToTopLeft.
                self invalidate.
                self contentsChanged.
            ]
        ].
    ].
!

image
    "return the image"

    ^ image
!

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

"/    image ~= anImage ifTrue:[
        self setImage:anImage
"/    ]
!

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

    |oldSize newSize|

    oldSize := image ifNil:[0@0] ifNotNil:[image extent].

    image := anImage.
    magnifiedImage := nil.
    self generateMagnifiedImage.

    newSize := image ifNil:[0@0] ifNotNil:[(magnifiedImage ? image) extent].
    self scrollToTopLeft.

    oldSize ~= newSize ifTrue:[
        "/ avoid endless loop in case of a resize happening due
        "/ to scrollBar visibility changes.
        "/ that QuerySignal suppresses another magnification in sizeChanged: 
        DoNotMagnifyQuery answer:true
        do:[
            self contentsChanged.
        ]
    ].

    shown ifTrue:[
        self clear.
        self invalidate
    ].
    self changed:#image.

    "Modified: / 10.2.2000 / 23:25:51 / cg"
!

tileMode:aBoolean tileOffset:aPoint

    tileMode := aBoolean.
    tileOffset := aPoint
! !

!ImageView methodsFor:'accessing - channels'!

imageChannel
    imageChannel isNil ifTrue:[
        imageChannel := ValueHolder new.
        imageChannel addDependent:self.
    ].
    ^ imageChannel

    "Created: / 11.2.2000 / 00:34:44 / cg"
!

imageChannel:aValueHolder
    imageChannel notNil ifTrue:[
        imageChannel removeDependent:self.
    ].
    imageChannel := aValueHolder.
    imageChannel notNil ifTrue:[
        imageChannel addDependent:self.
    ].

    "Created: / 11.2.2000 / 00:34:33 / cg"
! !

!ImageView methodsFor:'change & update'!

update:something with:aParameter from:changedObject
    something == imageChannel ifTrue:[
        self image:(imageChannel value).
        ^ self
    ].
    super update:something with:aParameter from:changedObject

    "Created: / 11.2.2000 / 00:37:02 / cg"
! !

!ImageView methodsFor:'drawing'!

generateMagnifiedImage
    |doFit innerWidth innerHeight imgWidth imgHeight|

    magnifiedImage notNil ifTrue:[
        ^ self
    ].
    image isNil ifTrue:[
        ^ self
    ].
        
    doFit := false.

    innerWidth := self innerWidth.
    innerHeight := self innerHeight.

    imgWidth := image width.
    imgHeight := image height.

    tileMode ~~ true ifTrue:[
        ((imgWidth > innerWidth)
        or:[imgHeight > innerHeight]) ifTrue:[
            ((adjust == #fit) or:[adjust == #fitBig]) ifTrue:[
                doFit := true
            ].
        ] ifFalse:[
            ((imgWidth < innerWidth)
            or:[imgHeight < innerHeight]) ifTrue:[
                ((adjust == #fit) or:[adjust == #fitSmall]) ifTrue:[
                    doFit := true
                ].
            ]
        ].
    ].
    doFit ifTrue:[
        magnifiedImage := image magnifiedPreservingRatioTo:(innerWidth @ innerHeight).
"/        self contentsChanged.
    ] ifFalse:[
        magnifiedImage := image
    ].
!

redrawX:x y:y width:w height:h
    |xI yI depth shownImage imgWidth imgHeight right bott|

    image notNil ifTrue:[
        self generateMagnifiedImage.

        shownImage := magnifiedImage ? image.
        imgWidth := shownImage width.
        imgHeight := shownImage height.

        adjust == #center ifTrue:[
            xI := (width - (margin * 2) - imgWidth) // 2.
            yI := (height - (margin * 2) - imgHeight) // 2.
        ] ifFalse:[
            xI := yI := margin
        ].

        ((depth := shownImage depth) == 1) ifTrue:[
            self paint:(shownImage colorFromValue:1)
                    on:(shownImage colorFromValue:0).
        ].

        tileMode == true ifTrue:[
            (depth == 1
            and:[image mask isNil]) ifFalse:[
                self clearRectangleX:x y:y width:w height:h.
                0 to:y+h by:tileOffset y do:[:oY |
                    0 to:x+w by:tileOffset x do:[:oX |
                        self displayForm:image x:oX y:oY 
                    ]
                ].
            ] ifTrue:[
                0 to:y+h by:tileOffset y do:[:oY |
                    0 to:x+w by:tileOffset x do:[:oX |
                        self displayOpaqueForm:image x:oX y:oY 
                    ]
                ].
            ].
        ] ifFalse:[
            (depth == 1
            and:[shownImage mask isNil]) ifFalse:[
                self clearRectangleX:x y:y width:w height:h.
                self displayForm:shownImage x:xI y:yI 
            ] ifTrue:[
                self displayOpaqueForm:shownImage x:xI y:yI 
            ].

            "/ right of image ?
            right := x + w - 1.
            right > (xI + imgWidth) ifTrue:[
                self clearRectangleX:(xI + imgWidth)
                                   y:y
                               width:(right - imgWidth - xI)
                              height:h  
            ].
            "/ below of image ?
            bott := y + h - 1.
            bott > (yI + imgHeight) ifTrue:[
                self clearRectangleX:margin
                                   y:(yI + imgHeight)
                               width:w
                              height:(bott - imgHeight - yI)  
            ].
        ].
    ]

    "Created: / 11.7.1996 / 21:02:12 / cg"
    "Modified: / 12.8.1998 / 14:02:28 / cg"
! !

!ImageView methodsFor:'event handling'!

sizeChanged:how
    magnifiedImage notNil ifTrue:[
        DoNotMagnifyQuery query ifFalse:[
            magnifiedImage := nil.
            self generateMagnifiedImage.
            self clear.
            self invalidate.
        ]
    ].
    super sizeChanged:how
! !

!ImageView methodsFor:'initialize / release'!

destroy
    image := nil.
    super destroy.
! !

!ImageView methodsFor:'queries'!

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

    image isNil ifTrue:[^ 0].
    ^ (magnifiedImage ? image) height
!

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

    image isNil ifTrue:[^ 0].
    ^ (magnifiedImage ? image) width
! !

!ImageView class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libwidg2/ImageView.st,v 1.53 2002-12-10 10:46:23 cg Exp $'
! !

ImageView initialize!