ImageView.st
author Claus Gittinger <cg@exept.de>
Thu, 30 Jun 2011 21:15:12 +0200
changeset 4043 532a328a9e0e
parent 4031 4213ffa8fc14
child 4066 a2fe2f6cf0c7
permissions -rw-r--r--
changed: #buttonMultiPress:x:y: common code for doubleClick !

"
 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 tileMode tileOffset lastMousePoint'
	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 a (bitmap-)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:'../../goodies/bitmaps/gifImages/garfield.gif'
        ImageView openOn:'../../goodies/bitmaps/SBrowser.xbm'

        ImageView openOnImage:(Image fromFile:'../../goodies/bitmaps/gifImages/garfield.gif')
        ImageView openOnImage:(Image fromFile:'../../goodies/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
"
!

examples
"
    |top imgView scrView|

    top := StandardSystemView new.
    top extent:300@300.

    imgView := ImageView new.
    imgView image:(Image fromFile:'../../goodies/bitmaps/gifImages/garfield.gif').

    scrView := HVScrollableView forView:imgView.
    scrView origin:0@0 corner:1.0@1.0.
    top add:scrView.

    top open.
"
! !

!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 or unsupported image format.'
        ] ifFalse:[
            e := 'No such image file.'.
        ].
        self warn:(self resources string: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/misc_icons/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 := anImage fileName ? 'an Image'
    ] ifFalse:[
        anImage isNil 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: / 01-06-2010 / 18:31:14 / 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.
        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"

    self image:anImage scroll:true
!

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

    self setImage:anImage scroll:doScroll
!

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

    self setImage:anImage scroll:doScroll invalidate:doInvalidate
!

magnification
    magnifiedImage isNil ifTrue:[^ 1@1].
    ^ magnifiedImage extent / image extent
!

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

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

    self setImage:anImage scroll:doScroll invalidate:true
!

setImage:anImage scroll:doScroll invalidate:doInvalidate
    "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].
    doScroll ifTrue:[
        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 and:[doInvalidate]) 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
    ^ self model

    "Modified: / 31-03-2011 / 10:45:58 / cg"
!

imageChannel:aValueHolder
    self model:aValueHolder.

    "Created: / 11-02-2000 / 00:34:33 / cg"
    "Modified: / 31-03-2011 / 10:46:07 / cg"
! !

!ImageView methodsFor:'change & update'!

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

    "Created: / 11-02-2000 / 00:37:02 / cg"
    "Modified: / 31-03-2011 / 10:46:16 / cg"
!

updateFromModel
    "the model changes, set my image"

    self image:model value.
! !

!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:[
            (tileOffset y > 0 and:[tileOffset x > 0]) 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:[
            xI > (x+w) ifTrue:[^ self]. "/ no need to draw
            yI > (y+h) ifTrue:[^ self]. "/ no need to draw
            (xI+imgWidth) < x ifTrue:[^ self]. "/ no need to draw
            (yI+imgHeight) < y ifTrue:[^ self]. "/ no need to draw

            (depth ~~ 1
            or:[shownImage mask notNil]) ifTrue:[
                self clearRectangleX:x y:y width:w height:h.
                shownImage displayOn:self x:xI y:yI.
                "/ self displayForm:shownImage x:xI y:yI 
            ] ifFalse:[
                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'!

buttonMotion:state x:x y:y
    |delta mousePoint|

    lastMousePoint notNil ifTrue:[
        mousePoint := (x@y).
        delta := mousePoint - lastMousePoint.
        delta ~= (0@0) ifTrue:[
            self scrollTo:(self viewOrigin - delta).
            lastMousePoint := mousePoint.
        ]
    ] ifFalse:[
        super buttonMotion:state x:x y:y
    ]
!

buttonPress:button x:x y:y
    button == 1 ifTrue:[
        "/ self cursor:(Cursor handGrab)
        lastMousePoint := x@y.
    ].
    super buttonPress:button x:x y:y
!

buttonRelease:button x:x y:y
    button == 1 ifTrue:[
        lastMousePoint := nil
    ].
    super buttonRelease:button x:x y:y
!

sizeChanged:how
    (#(fit fitBig fitSmall) includes:adjust) ifTrue:[
        magnifiedImage notNil ifTrue:[
            DoNotMagnifyQuery query ifFalse:[
                magnifiedImage := nil.
                self generateMagnifiedImage.
                self clear.
                self invalidate.
            ]
        ].
    ] ifFalse:[
        adjust == #center ifTrue:[
            self clear.
            self invalidate.
        ].
    ].
    super sizeChanged:how
! !

!ImageView methodsFor:'initialization & release'!

destroy
    image := magnifiedImage := 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 methodsFor:'scrolling'!

scrollToMakeVisible:aPoint
    "try to arrange for aPoint to be visible (at the center, if possible)"

    |mag pos|

    mag := self magnification.
    pos := aPoint * mag.
    self scrollTo:(pos - (self extent / 2)) rounded.
! !

!ImageView class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libwidg2/ImageView.st,v 1.75 2011-03-31 12:15:55 cg Exp $'
!

version_CVS
    ^ '$Header: /cvs/stx/stx/libwidg2/ImageView.st,v 1.75 2011-03-31 12:15:55 cg Exp $'
! !

ImageView initialize!