ImageEditView.st
author Claus Gittinger <cg@exept.de>
Tue, 13 May 2003 19:44:09 +0200
changeset 2507 7344d9245472
parent 2490 62230519175a
child 2508 ffb079bfe8b6
permissions -rw-r--r--
*** empty log message ***

"
 COPYRIGHT (c) 1997 by eXept Software AG
	      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' }"

ImageView subclass:#ImageEditView
	instanceVariableNames:'magnification imageReaderClass resourceClass resourceSelector
		mouseKeyColorMode undoImages modified editMode lastPastePoint
		imageInfoHolder activityInfoHolder pickedColorHolder
		drawingColors drawingPixels drawingColorHolders
		drawingPixelHolders clickInfoCallBack'
	classVariableNames:'Clipboard ClipboardMagnified LastMagnification
		GridMagnificationLimit MaxUndos LastSaveDirectory LastSaveClass'
	poolDictionaries:''
	category:'Views-Misc'
!

!ImageEditView class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1997 by eXept Software AG
	      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
"
    The ImageEditView is a view class which can be used by applications
    like the Image Editor for modifying or inspecting images.

    [see also:]
	ImageEditor Image

    [author:]
	Thomas Zwick
"
! !

!ImageEditView class methodsFor:'initialization'!

initialize
    MaxUndos := 5.
    GridMagnificationLimit := 8 @ 8.

    "
     self initialize
    "
! !

!ImageEditView class methodsFor:'accessing'!

gridMagnificationLimit
    ^ GridMagnificationLimit
!

gridMagnificationLimit:anInteger
    GridMagnificationLimit := anInteger
! !

!ImageEditView class methodsFor:'helpers'!

copyImageToClipboard:copiedImage
    ClipboardMagnified := nil.
    Clipboard := copiedImage.
! !

!ImageEditView methodsFor:'accessing'!

activityInfoHolder
    "return the value of the instance variable 'activityInfoHolder' (automatically generated)"

    ^ activityInfoHolder

    "Created: / 29.7.1998 / 18:49:39 / cg"
!

activityInfoHolder:something
    "set the value of the instance variable 'activityInfoHolder' (automatically generated)"

    activityInfoHolder := something.

    "Created: / 29.7.1998 / 18:49:39 / cg"
!

clickInfoCallBack:aTwoArgBlock
     clickInfoCallBack := aTwoArgBlock

    "Created: / 10.2.2000 / 23:07:14 / cg"
!

clipBoard
    ^ Clipboard
!

drawingColors:anArrayTwoColors
    (drawingColorHolders at:1) value:(anArrayTwoColors at:1).
    (drawingColorHolders at:2) value:(anArrayTwoColors at:2).
!

imageInfoHolder
    "return the value of the instance variable 'imageInfoHolder' (automatically generated)"

    ^ imageInfoHolder

    "Created: / 29.7.1998 / 18:29:50 / cg"
!

imageInfoHolder:something
    "set the value of the instance variable 'imageInfoHolder' (automatically generated)"

    imageInfoHolder := something.

    "Created: / 29.7.1998 / 18:29:50 / cg"
!

magnification

    ^magnification

!

magnification: aPoint
    |oldOrg|

    magnification ~= aPoint
    ifTrue:
    [
	oldOrg := self viewOrigin / magnification.
	magnification := aPoint asPoint.

	self scrollTo:(oldOrg * magnification) rounded redraw:false.        
"/        self scrollToTopLeft.
	self contentsChanged.
	self invalidate.
	ClipboardMagnified := nil.
    ]

    "Modified: / 31.7.1998 / 02:38:47 / cg"
!

resourceClass

    ^resourceClass
!

resourceClass: aClassOrSymbol

    resourceClass := aClassOrSymbol isClass ifTrue: [aClassOrSymbol name] ifFalse: [aClassOrSymbol asSymbol]
!

resourceMessage

    ^resourceClass, ' ', resourceSelector
!

resourceMessage: aString

    (aString isString and: [aString trimBlanks size > 0])
    ifTrue:
    [
	resourceClass := (aString readStream upTo: Character space) asSymbol.
	resourceSelector := (aString copy reverse readStream upTo: Character space) reverse asSymbol
    ]
    ifFalse:
    [
	^nil
    ]

   
!

resourceSelector

    ^resourceSelector
!

resourceSelector: aStringOrSymbol

    resourceSelector := aStringOrSymbol asSymbol
!

selectedColor
   ^ (drawingColorHolders at:mouseKeyColorMode) value
!

selectedColor: aColor
    (drawingColorHolders at:mouseKeyColorMode) value:aColor
!

selectedColorIndex

   ^ (drawingPixelHolders at:mouseKeyColorMode) value
!

selectedColorIndex: aPixelIndex
    (drawingPixelHolders at:mouseKeyColorMode) value: aPixelIndex
!

undoImages

   ^undoImages
! !

!ImageEditView methodsFor:'drawing'!

drawFrame

    self paint:Color black.
    self lineWidth: (magnification x//3 min: 3).
    self displayRectangle: ((0@0) extent:(image extent * magnification) + margin).
    self lineWidth:1.
!

drawFramesIn: aRectangle

    magnification >= GridMagnificationLimit
    ifTrue:
    [   
        |origin lineStartingPoint lineEndingPoint oldColor|
        origin := aRectangle origin - 1.
        lineStartingPoint := origin + (0@magnification y).
        lineEndingPoint   := lineStartingPoint + (aRectangle width@0).
        oldColor := self paint.
        self xoring:
        [
            self displayLineFrom: lineStartingPoint to: lineEndingPoint.
            lineStartingPoint x to: lineStartingPoint x + aRectangle width - magnification x by: magnification x do:
            [:x|   
                self displayLineFrom: x@(origin y) to: x@(origin y + magnification y)
            ].
        ].
        self paint: oldColor.
    ]



!

drawPasteRectangleAt: aPoint

    |currentPoint gridCorrection extent org|

    magnification >= GridMagnificationLimit ifFalse: [gridCorrection := 0] ifTrue: [gridCorrection := 1].
    currentPoint := aPoint // magnification*magnification + margin. 

    self repairDamage.

    currentPoint ~= lastPastePoint ifTrue:[              
        ClipboardMagnified isNil ifTrue:[
            ClipboardMagnified := (Clipboard magnifiedBy: magnification) onDevice: device
        ].   

        extent       := ClipboardMagnified extent.

        "/ currentPoint := currentPoint - self viewOrigin.

        self redraw: (((lastPastePoint ? currentPoint)"-self viewOrigin") extent: extent).
        self repairDamage.

false "        (extent x > 400 or: [extent y > 400])" ifTrue:[
            self xoring: [
                self fillRectangle: (currentPoint extent: extent)
            ]   
        ] ifFalse:[
            ClipboardMagnified notNil ifTrue:[
                self displayDeviceForm: ClipboardMagnified 
                                     x: currentPoint x - self viewOrigin x 
                                     y: currentPoint y - self viewOrigin y.
            ].
            editMode == #pasteUnder ifTrue:[
                self redrawImageX:currentPoint x y:currentPoint y width:extent x height:extent y unmaskedOnly:true
            ]
        ]  
    ]. 
    lastPastePoint := currentPoint.

    "Modified: / 18.5.1999 / 20:23:33 / cg"
!

fillFramedRectangle: aRectangle

    self fillRectangle: aRectangle.
    self drawFramesIn: aRectangle
!

redraw:aRectangle
    self invalidate:(aRectangle origin "+ self viewOrigin" extent:aRectangle extent). 
"/    super redraw:(aRectangle origin + self viewOrigin extent:aRectangle extent).

    "Modified: / 15.11.2001 / 16:43:53 / cg"
!

redrawImageX:x y:y width:w height:h
    self redrawImageX:x y:y width:w height:h unmaskedOnly:false

    "Modified: / 18.5.1999 / 20:14:03 / cg"
!

redrawImageX:x y:y width:w height:h unmaskedOnly:unmaskedOnly

    |ih iw magX magY minX maxX minY maxY 
     color lastColor lastY runW x0 xI yI maskColor mask
     sizeOfMaskPoint useNearestColor|

    useNearestColor := device visualType == #PseudoColor.

    mask := image mask.
    ih := image height.
    iw := image width.
    magX := magnification x.
    magY := magnification y.

    minX := (x // magX - 1) max: 0.
    minX >= iw ifTrue:[minX := (iw - 1) max: 0].
    minY := (y // magY - 1) max: 0.
    minY >= ih ifTrue:[minY := (ih - 1) max: 0].
    maxX := (x + w) // magX + 1.
    maxX > iw ifTrue:[maxX := iw].
    maxY := (y + h) // magY + 1.
    maxY > ih ifTrue:[maxY := ih].

    lastY := -1.

    x0 := minX.
    runW := 0.
    maskColor := false.
    sizeOfMaskPoint := magnification//3.
    image 
        colorsFromX:minX y:minY toX:maxX-1 y:maxY-1 
        do:[:xx :yy :color|

            shown ifFalse:[^ self].

            yy ~~ lastY ifTrue:[
                runW ~~ 0 ifTrue:[
                    |origin|

                    origin := (x0 * magX + margin)@(lastY * magY + margin).
                    (unmaskedOnly not or:[maskColor not]) ifTrue:[
                        self fillFramedRectangle: (origin extent: (runW@magY)).                    
                        maskColor ifTrue:[
                            self xoring: [self fillRectangle: (origin + sizeOfMaskPoint extent: sizeOfMaskPoint)]
                        ]
                    ].
                    runW := 0.
                ]. 
                x0 := xx.
                lastY := yy.
            ]. 

            color ~= lastColor ifTrue:[
                runW ~~ 0 ifTrue:[
                    |origin|
                    origin := (x0 * magX + margin)@(yy * magY + margin).
                    (unmaskedOnly not or:[maskColor not]) ifTrue:[
                        self fillFramedRectangle: (origin extent: (runW@magY)).
                        maskColor ifTrue:[
                            self xoring: [self fillRectangle: (origin + sizeOfMaskPoint extent: sizeOfMaskPoint)]
                        ].
                    ].
                    runW := 0.
                ].

                lastColor := color.
                useNearestColor ifTrue:[
                    lastColor := lastColor nearestOn:device
                ].
                self paint:lastColor.
                mask notNil ifTrue:[  
                    maskColor := false.
                    (mask pixelAtX:xx y:yy) == 0 ifTrue:[
                        unmaskedOnly ifFalse:[
                            self paint: (lastColor := self viewBackground).
                        ].
                        maskColor := true.
                    ].
                    lastColor := nil.
                ].
                runW := 0.
                x0 := xx.
            ].  
            runW := runW + magX
        ].

    runW ~~ 0 ifTrue:[
        |origin|

        origin := (x0 * magX + margin)@(lastY * magY + margin).
        (unmaskedOnly not or:[maskColor not]) ifTrue:[
            self fillFramedRectangle: (origin extent: runW@magY).
            maskColor ifTrue:[
                self xoring:[
                    self fillRectangle: (origin + sizeOfMaskPoint extent: sizeOfMaskPoint)
                ]
            ].
        ]
    ].

    "Created: / 18.5.1999 / 20:13:39 / cg"
    "Modified: / 18.5.1999 / 20:36:20 / cg"
!

redrawX:x y:y width:w height:h

    |ih iw xI yI devImage imgWidth imgHeight|

    image isNil ifTrue:[^self].

    magnification = (1@1) ifTrue: [
        Object errorSignal handle:[:ex |
            Transcript showCR:'cannot convert image: ', ex description.
        ] do:[
            devImage := image onDevice:device.
            devImage ~~ image ifTrue:[
                image := devImage.
                self changed:#image.
            ].
        ].
        image device == device ifTrue:[
            ^ super redrawX:x y:y width:w height:h
        ].
    ].

    self clippingRectangle: (x@y extent:w@h).

    self redrawImageX:x y:y width:w height:h.

    "/ right of image ?
    adjust == #center ifTrue:
    [
        xI := (width - ih) // 2 - margin.
        yI := (height - iw) // 2 - margin.
    ]
    ifFalse:
    [
        xI := yI := margin
    ].

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

    (x + w - 1) > (xI + (magnification x * imgWidth)) ifTrue:
    [
        self clearRectangleX:(xI + (magnification x * imgWidth))
                           y:y
                       width:(x + w - (magnification x * imgWidth) - xI)
                      height:h
    ].
    (y + h - 1) > (yI + (magnification y * imgHeight)) ifTrue:
    [
        self clearRectangleX:margin
                           y:(yI + (magnification y * imgHeight))
                       width:w
                      height:(y + h - (magnification y * imgHeight) - yI)  
    ].
    self drawFrame.
    self clippingRectangle: nil.

    "Modified: / 31.7.1998 / 02:22:45 / cg"
! !

!ImageEditView methodsFor:'edit modes'!

editMode

    ^editMode
!

editMode: anEditModeSymbol

    editMode := anEditModeSymbol
!

mouseKeyColorMode

    ^mouseKeyColorMode printString
!

mouseKeyColorMode:aMode

    mouseKeyColorMode := aMode
! !

!ImageEditView methodsFor:'event handling'!

buttonMotion:state x:x y:y

    |p|

    (x < 0 or:[y < 0]) ifTrue:[
        ^ self
    ].

    p := x@y.

    state ~~ 0 ifTrue:[
        ("self selectedColor notNil" true 
        and:[(self imageContainsPoint:p) 
        and:[editMode == #point]])
        ifTrue:[
            self pointAt:p.
            ^ self
        ].
        self drawCursorAt:p.
    ] ifFalse:[
"/ Transcript showCR:'m'.
        self drawCursorAt:p.
        (editMode startsWith:#paste) ifTrue: [
"/ Transcript show:'p '; showCR:(self imageContainsPastePoint:p).
            ("self selectedColor notNil" true and: [self imageContainsPastePoint:p]) 
                ifTrue:  [self drawPasteRectangleAt:p]
                ifFalse: [self cursor:Cursor stop. self releasePasteDrawing]
        ]
    ]

    "Modified: / 10.2.2000 / 22:03:18 / cg"
!

buttonPress:button x:x y:y
    |p mouseButtonColorToolBar clr masked|

    p := x@y.

    self drawCursorAt:p.

    ("self selectedColor notNil" true 
    and: [self imageContainsPoint:p])
    ifTrue:[   
        self sensor shiftDown ifTrue:[
            (image maskAt:(p // magnification)) == 0 ifTrue:[
                masked := true.
            ] ifFalse:[
                masked := false.
                clr := image colorAt:(p // magnification).
            ].
            pickedColorHolder notNil ifTrue:[
                "/ select the color under the cursor, place it into the
                "/ pickedColorHolder/
                pickedColorHolder value:clr.
            ].
            self selectedColor:clr.
            masked ifTrue:[self selectedColorIndex:nil].
            self changed:#selectedColor with:clr.
        ] ifFalse:[
            mouseKeyColorMode := button.
            self makeUndo.

"/            "/ cg: what a kludge - please change to use a valueHolder,
"/            "/ which gets the information ...
"/            mouseButtonColorToolBar := masterApplication builder componentAt: #MouseButtonColorToolBar.
"/            mouseButtonColorToolBar notNil ifTrue:[
"/                (mouseButtonColorToolBar itemAt: mouseKeyColorMode) toggleIndication.
"/                mouseButtonColorToolBar do: [:i| i updateIndicators].
"/            ].

            clickInfoCallBack notNil ifTrue:[
                "/ still a kludge, but less ugly ...
                clickInfoCallBack value:button value:p
            ].
            "/ editMode is something like #point, #rectangle etc.
            self perform: (editMode, 'At:') asSymbol with:p
        ]
    ]

    "Modified: / 10.2.2000 / 23:11:33 / cg"
!

buttonRelease:button x:x y:y

    self drawCursorAt: x@y.

    ("self selectedColor notNil" true and: [self imageContainsPoint: x@y])
    ifTrue: [   
        image release.

"/        "/ cg: what a kludge - please change to use a valueHolder,
"/        "/ which gets the information ...
"/        masterApplication imagePreView invalidate.

        "/ cg: still a kludge - but less ugly
        self changed:#subImageIn with:(image bounds).
    ]

    "Modified: / 10.2.2000 / 23:41:41 / cg"
!

pointerLeave:state

    super pointerLeave: state.

    self updateImageInfo: self imageInfoString.
    self cursor:Cursor normal.

    (editMode startsWith:#paste) ifTrue: [
        self releasePasteDrawing
    ]

    "Modified: / 29.7.1998 / 18:27:42 / cg"
! !

!ImageEditView methodsFor:'image - dragging & info'!

dragRectangleStartingAt: aPointIn emphasis: emphasis
    "drag a rectangle (filled or unfilled)"

    |currentPoint currentExtent firstPoint lastCurrentPoint gridCorrection 
     mp lastMp p whichQuarter scrollX scrollY aPoint|

    aPoint := aPointIn.
    firstPoint := currentPoint := lastCurrentPoint :=  aPoint//magnification*magnification.
    magnification >= GridMagnificationLimit ifFalse: [gridCorrection := 0] ifTrue: [gridCorrection := 1].

    [device anyButtonPressed] whileTrue: [                                                  
        mp := self sensor mousePoint.
        mp = lastMp ifTrue:[
            Delay waitForSeconds:0.05
        ] ifFalse:[
            lastMp := mp.
            mp := device translatePoint:mp fromView:nil toView:self.
            "/ mp is a device coordinate here ...
            scrollX := 0.
            mp x > width ifTrue:[
                scrollX := mp x - width.
            ] ifFalse:[
                mp x < 0 ifTrue:[
                    scrollX := mp x.
                ]
            ].
            scrollY := 0.
            mp y > height ifTrue:[
                scrollY := mp y - height.
            ] ifFalse:[
                mp y < 0 ifTrue:[
                    scrollY := mp y.
                ]
            ].
            (scrollX + scrollY) ~~ 0 ifTrue:[
                self scrollTo:(self viewOrigin + (scrollX @ scrollY)).
                lastMp := nil.
            ].

            mp := mp + self viewOrigin.
            "/ mp is now a logical coordinate.

            currentPoint := (0@0) max: (image extent * magnification min: (p := mp)).
            currentPoint := currentPoint//magnification*magnification.
            currentExtent := (firstPoint - currentPoint) abs.
            whichQuarter := (firstPoint x - currentPoint x) > 0 
                 ifTrue:  [(firstPoint y - currentPoint y) > 0 ifTrue: ["4"1@1] ifFalse: ["3"1@0]]
                 ifFalse: [(firstPoint y - currentPoint y) > 0 ifTrue: ["1"0@1] ifFalse: ["2"0@0]].

            self drawCursorAt: p withLabel: 
                ((firstPoint//magnification - whichQuarter + 1) printString, 
                ' to: ', 
                (currentPoint//magnification + whichQuarter) printString),
                ' (extent: ',
                (currentExtent//magnification) printString, ')'.

            currentPoint ~= lastCurrentPoint ifTrue:[   
                emphasis = #inverseFilledBox ifTrue: [
                    self redraw: ((firstPoint min: lastCurrentPoint) - 1 extent: (firstPoint - lastCurrentPoint) abs + 2).
                    self xoring: [self fillRectangle: ((firstPoint min: currentPoint) + margin extent: currentExtent - gridCorrection)]
                ].
                emphasis = #box
                ifTrue:[
                    |origin extent lineWidthY lineWidthX|
                    origin := (firstPoint min: lastCurrentPoint) - 1.
                    extent := (firstPoint - lastCurrentPoint) abs + 2.
                    lineWidthY := extent y min: (magnification y + 2).
                    lineWidthX := extent x min: (magnification x + 2).
                    self redraw: (origin extent: (extent x@lineWidthY)).
                    self redraw: ((origin x@(origin y + extent y - lineWidthY)) extent: (extent x@lineWidthY)).
                    self redraw: ((origin x@(origin y + lineWidthY)) extent: (lineWidthX@(0 max: (extent y - (lineWidthY * 2))))).
                    self redraw: (((origin x + extent x - lineWidthX)@(origin y + lineWidthY)) extent: (lineWidthX@(extent y - (lineWidthY * 2)))).
                    self selectedColor ~= Color noColor
                        ifTrue: [self paint: self selectedColor]
                        ifFalse: [self paint: self viewBackground]. 
                    origin := (firstPoint min: currentPoint) + margin.
                    extent := currentExtent - gridCorrection.
                    lineWidthY := extent y min: magnification y.
                    lineWidthX := extent x min: magnification x.
                    (lineWidthY > 0 and: [lineWidthX > 0])
                    ifTrue:[
                        self fillRectangle: (origin extent: (extent x@lineWidthY)).
                        self fillRectangle: ((origin x@(origin y + extent y - lineWidthY)) extent: (extent x@lineWidthY)).
                        self fillRectangle: ((origin x@(origin y + lineWidthY)) extent: (lineWidthX@(0 max: (extent y - (lineWidthY * 2))))).
                        self fillRectangle: (((origin x + extent x - lineWidthX)@(origin y + lineWidthY)) extent: (lineWidthX@(extent y - (lineWidthY * 2)))).
                    ]
                ].
                emphasis = #filledBox
                ifTrue:[
                    self redraw: ((firstPoint min: lastCurrentPoint) - 1 extent: (firstPoint - lastCurrentPoint) abs + 2).
                    self selectedColor ~= Color noColor
                        ifTrue: [self paint: self selectedColor]
                        ifFalse: [self paint: self viewBackground].
                    self fillRectangle: ((firstPoint min: currentPoint) + margin extent: currentExtent - gridCorrection).
                ].
            ]. 
            lastCurrentPoint := currentPoint.
        ].                  
    ].                  

    ^((0@0) max: (firstPoint min: currentPoint)) extent: (firstPoint - currentPoint) abs

    "Created: / 21.8.1998 / 20:17:07 / cg"
    "Modified: / 10.10.2001 / 14:13:08 / cg"
!

drawCursorAt:aPoint
    |clr imgPoint r g b|

    image isNil ifTrue: [
        self updateImageInfo: self imageInfoString. 
        self cursor:Cursor stop.
        ^ self
    ].

    imgPoint := aPoint // magnification.
    ((imgPoint x between:0 and:(image width-1)) 
    and:[imgPoint y between:0 and: (image height-1)])
    ifFalse:[
        self updateImageInfo: self imageInfoString. 
        self cursor:Cursor stop.
    ] ifTrue: [
        clr := image colorAt:imgPoint.
        r := clr redByte.
        g := clr greenByte.
        b := clr blueByte.
        self updateImageInfo: imgPoint printString 
                        , ' (r:' 
                        , r printString
                        , ' g:' , g printString
                        , ' b:' , b printString
                        , ' #' , (r hexPrintString:2) , (g hexPrintString:2) , (b hexPrintString:2)
                        , ' pixel:' , (image pixelAt:imgPoint) printString
                        , ')'.
        self cursor:Cursor crossHair
    ].

    "Modified: / 29.7.1998 / 18:26:01 / cg"
!

drawCursorAt: aPoint withLabel: aLabel

    ((0@0 extent: image extent * magnification) containsPoint: aPoint)
	 ifFalse:[self cursor:Cursor stop]
	 ifTrue: [self cursor:Cursor crossHair].
     self updateImageInfo: aLabel.

    "Modified: / 29.7.1998 / 18:26:04 / cg"
!

updateActivity: something
    |msg|

    msg := something printString.

    "/ cg: new code:
    activityInfoHolder notNil ifTrue:[
	activityInfoHolder value:msg.
    ].

    "Modified: / 29.7.1998 / 18:41:47 / cg"
!

updateImageInfo: something
    |msg coordLabel|

    msg := something printString.

    "/ cg: new code:
    imageInfoHolder notNil ifTrue:[
	msg ~= imageInfoHolder value ifTrue:[
	    imageInfoHolder value:msg.
	].
	^ self
    ].

"/    "/ cg: what a kludge - please change to use a valueHolder,
"/    "/ which gets the coordinate ...
"/
"/    (masterApplication respondsTo: #coordLabel)
"/    ifTrue:[  
"/        coordLabel := masterApplication coordLabel.
"/
"/        coordLabel label ~= msg
"/        ifTrue:[         
"/            coordLabel label: msg.
"/            "/ coordLabel redraw
"/        ]
"/    ]

    "Modified: / 29.7.1998 / 19:00:21 / cg"
! !

!ImageEditView methodsFor:'image editing'!

boxAt: aPoint
    "draw a rectangular outline with the currently selected color"

    |choosedBox imageBox clr|

    (clr := self selectedColor) notNil ifTrue:[
        choosedBox := self dragRectangleStartingAt: aPoint emphasis: #box.
        imageBox := choosedBox origin//magnification extent: (choosedBox extent//magnification).
        image drawRectangle:imageBox withColor:clr.
        image restored.
        self redraw: (choosedBox expandedBy: 1).

"/        "/ cg: what a kludge - please change to use a valueHolder,
"/        "/ which gets the information ...
"/        masterApplication imagePreView redraw: (imageBox expandedBy: 1).

        "/ cg: still a kludge - but less ugly
        self changed:#subImageIn with:(imageBox expandedBy: 1).

        modified := true
    ].

    "Modified: / 10.2.2000 / 23:42:08 / cg"
!

copyAt: aPoint
    |choosenBox r box copiedImage|

    choosenBox := self dragRectangleStartingAt: aPoint emphasis: #inverseFilledBox.
    box := choosenBox origin // magnification extent: (choosenBox extent // magnification).
    copiedImage := image subImageIn: box.

    self class copyImageToClipboard:copiedImage.

    r := (choosenBox expandedBy:1).
    self redraw:r

    "Modified: / 21.8.1998 / 20:16:41 / cg"
!

copyImageToClipboard
    self class copyImageToClipboard:image.
!

cropLeft:doLeft right:doRight top:doTop bottom:doBottom
    |yMinNew yMaxNew xMinNew xMaxNew
     pix stillCrobbing xMax yMax x y|

    xMax := image width - 1.
    yMax := image height - 1.

    xMinNew := 0.
    doLeft ifTrue:[
        pix := image pixelAtX:xMinNew y:0.
        stillCrobbing := true.
        [stillCrobbing] whileTrue:[
            0 to:yMax do:[:y |
                (image pixelAtX:xMinNew y:y) ~~ pix ifTrue:[
                    stillCrobbing := false
                ]
            ].
            stillCrobbing ifTrue:[
                xMinNew := xMinNew + 1.
                xMinNew >= image width ifTrue:[
                    self warn:'Image is all the same color - no crob.'.
                    ^ self
                ]
            ].
        ].
    ].

    xMaxNew := xMax.
    doRight ifTrue:[
        stillCrobbing := true.
        pix := image pixelAtX:xMaxNew y:0.
        [stillCrobbing] whileTrue:[
            0 to:yMax do:[:y |
                (image pixelAtX:xMaxNew y:y) ~~ pix ifTrue:[
                    stillCrobbing := false
                ]
            ].
            stillCrobbing ifTrue:[
                xMaxNew := xMaxNew - 1.
            ].
        ].
    ].

    yMinNew := 0.
    doTop ifTrue:[
        pix := image pixelAtX:xMinNew y:yMinNew.
        stillCrobbing := true.
        [stillCrobbing] whileTrue:[
            xMinNew to:xMaxNew do:[:x |
                (image pixelAtX:x y:yMinNew) ~~ pix ifTrue:[
                    stillCrobbing := false
                ]
            ].
            stillCrobbing ifTrue:[
                yMinNew := yMinNew + 1.
            ].
        ].
    ].

    yMaxNew := yMax.
    doRight ifTrue:[
        stillCrobbing := true.
        pix := image pixelAtX:xMaxNew y:yMaxNew.
        [stillCrobbing] whileTrue:[
            xMinNew to:xMaxNew do:[:x |
                (image pixelAtX:x y:yMaxNew) ~~ pix ifTrue:[
                    stillCrobbing := false
                ]
            ].
            stillCrobbing ifTrue:[
                yMaxNew := yMaxNew - 1.
            ].
        ].
    ].

    (xMinNew == 0
    and:[xMaxNew == (image width - 1)
    and:[yMinNew == 0
    and:[yMaxNew == (image height - 1)]]]) ifTrue:[
        self warn:'No border found - no crob.'.
        ^ self
    ].

"/    self warn:'extract subImage ' 
"/              , (xMinNew @ yMinNew) printString
"/              , ' -> '
"/              , (xMaxNew @ yMaxNew) printString.

    self makeUndo.
    self 
        makeSubImageX:xMinNew y:yMinNew 
        width:(xMaxNew - xMinNew + 1)
        height:(yMaxNew - yMinNew + 1)

    "Created: / 7.9.1998 / 14:25:52 / cg"
    "Modified: / 7.9.1998 / 16:35:35 / cg"
!

fillAt: aPoint
    "perform a flood-fill with the currently selected color"

    windowGroup withExecuteCursorDo:[
        |filledPoints clr|

        (clr := self selectedColor) notNil ifTrue:[
            self updateActivity:'Flood filling - press CTRL-y to abort ...'.
            [
                image floodFillAt: aPoint//magnification withColor:clr.
                image restored.

                self invalidate.

"/                "/ cg: what a kludge - please change to use a valueHolder,
"/                "/ which gets the information ...
"/                masterApplication imagePreView invalidate.

                "/ cg: still a kludge - but less ugly
                self changed:#subImageIn with:(image bounds).

                modified := true
            ] valueOnUnwindDo:[
                self updateActivity:'Flood fill aborted.'
            ].
        ].
        self updateActivity:''
    ]

    "Modified: / 10.2.2000 / 23:40:58 / cg"
!

filledBoxAt: aPoint
    "fill a rectangular area with the currently selected color"

    |choosedBox imageBox clr|

    (clr := self selectedColor) notNil ifTrue:[
        choosedBox := self dragRectangleStartingAt: aPoint emphasis: #filledBox.
        imageBox := choosedBox origin//magnification extent: (choosedBox extent//magnification).
        image fillRectangle:imageBox withColor:clr.
        image restored.
        self redraw: (choosedBox expandedBy: 1).

"/        "/ cg: what a kludge - please change to use a valueHolder,
"/        "/ which gets the information ...
"/        masterApplication imagePreView redraw: (imageBox expandedBy: 1).

        "/ cg: still a kludge - but less ugly
        self changed:#subImageIn with:(imageBox expandedBy: 1).

        modified := true
    ]

    "Modified: / 10.2.2000 / 23:37:04 / cg"
!

flipHorizontal

    self makeUndo.
    self image: image copy flipHorizontal

!

flipVertical

    self makeUndo.
    self image: image copy flipVertical

!

magnifyImageTo:newSize
    self makeUndo.
    self image: (image magnifiedBy: newSize/image extent)
!

makeBorderedImageX:newX y:newY width:newWidth height:newHeight
    |newImage oldWidth oldHeight|

    oldWidth := image width.
    oldHeight := image height.

    newImage := image class width:newWidth height:newHeight depth:image depth.
    newImage photometric:image photometric.
    newImage colorMap:image colorMap copy.
    newImage bits:(ByteArray new:(newImage bytesPerRow * newHeight)).

    image mask notNil
    ifTrue:[
        |newMaskImage|

        newMaskImage := Depth1Image width:newWidth height:newHeight.
        newMaskImage photometric: image mask photometric.
        newMaskImage colorMap: image mask colorMap copy.
        newMaskImage bits:(ByteArray new: newMaskImage bytesPerRow * newHeight).
        newImage mask: newMaskImage
    ].

    newImage copyFrom:image x:0 y:0 toX:newX y:newY width:oldWidth height:oldHeight.
    self makeUndo.
    self image:newImage.

    "Created: / 7.9.1998 / 13:00:16 / cg"
    "Modified: / 7.9.1998 / 14:15:32 / cg"
!

makeBrighter
    ^ self makeNewColorMapByMapping:[:clr | clr lightened].
!

makeDarker
    ^ self makeNewColorMapByMapping:[:clr | clr darkened].
!

makeGrayScale
    ^ self makeNewColorMapByMapping:[:clr | Color brightness:(clr brightness)].
!

makeInverse
    ^ self makeNewColorMapByMapping:[:clr | 
        Color red:(100-clr red) green:(100-clr green) blue:(100-clr blue)].
!

makeNewColorMapByMapping:functionOfColor
    |xMax yMax clr pix map revMap n_clr n_pix anyChange
     newColors newColorArray newImage|

    image colorMap isNil ifTrue:[
        self error:'image has no colormap'.
        ^ false
    ].

    anyChange := false.

    xMax := image width - 1.
    yMax := image height - 1.

    newColors := Set new.
    newColorArray := OrderedCollection new.
    map := Array new:256.
    revMap := OrderedCollection new.

    newImage := image class width:image width height:image height depth:image depth.
    newImage photometric:image photometric.
    "/ newImage colorMap:(image colorMap copy).
    newImage bits:(ByteArray new:(image bits size)).
    newImage mask:(image mask copy).

    0 to:yMax do:[:y |
        0 to:xMax do:[:x |
            pix := image pixelAtX:x y:y.
            (n_pix := map at:pix+1) isNil ifTrue:[
                clr := image colorAtX:x y:y.
                n_clr := functionOfColor value:clr.
                (newColors includes:n_clr) ifFalse:[
                    newColors add:n_clr.
                    newColorArray add:n_clr.
                    revMap add:pix.
                    map at:pix+1 put:(n_pix := revMap size - 1).
                ] ifTrue:[
                    "/ mhmh - multiple pixels mapped to the same color
                    n_pix := (newColorArray indexOf:n_clr) - 1.
                    map at:pix+1 put:n_pix.
                ]
            ].
            newImage pixelAtX:x y:y put:n_pix.
        ]
    ].

    newImage colorMap:(MappedPalette withColors:newColorArray).
    self makeUndo.
    self image:newImage.
    ^ true
!

makeSubImageX:oldX y:oldY width:newWidth height:newHeight
    |newImage|

    newImage := image class width:newWidth height:newHeight depth:image depth.
    newImage photometric:image photometric.
    newImage colorMap:image colorMap copy.
    newImage bits:(ByteArray new:(newImage bytesPerRow * newHeight)).

    image mask notNil
    ifTrue:[
        |newMaskImage|

        newMaskImage := Depth1Image width:newWidth height:newHeight.
        newMaskImage photometric: image mask photometric.
        newMaskImage colorMap: image mask colorMap copy.
        newMaskImage bits:(ByteArray new: newMaskImage bytesPerRow * newHeight).
        newImage mask: newMaskImage
    ].

    newImage copyFrom:image x:oldX y:oldY toX:0 y:0 width:newWidth height:newHeight.
    self image:newImage.

    "Created: / 7.9.1998 / 13:00:16 / cg"
    "Modified: / 7.9.1998 / 14:15:32 / cg"
!

negativeImage

    self makeUndo.
    self image: (image copy bits:(image bits invert))
!

pasteAt: aPoint
    "paste the image in the clipboard at aPoint"

    self pasteAt:aPoint mode:nil.
!

pasteAt: aPoint mode:modeSymbol
    "paste the image in the clipboard at aPoint"

    |answer anyColorMissing choosedBox imagePoint imgX imgY copiedImage imageBox newColorMap
     existingColors newColors allColors currentColorMap newColormap|

    Object errorSignal handle:[:ex|
        ex signal == Image unrepresentableColorSignal ifFalse:[
            ex reject
        ].
        self undo.
        self warn: 'Paste failed !!\Increasing the images depth might help.' withCRs. 
    ] do: [   
        windowGroup withExecuteCursorDo:[
            choosedBox := self dragRectangleStartingAt: aPoint emphasis: #inverseFilledBox.

            imagePoint := choosedBox origin//magnification.

            copiedImage := Clipboard copy.

            true "/ image photometric == #palette 
            ifTrue:[
                "/ for all colors in the pasted image,
                "/ check, if its in the colormap of the
                "/ target image.

                anyColorMissing := false.
                image colorMap notNil ifTrue:[
                    copiedImage usedValues do:[:pixel |
                        |pastedColor oldColorMap|

                        pastedColor := copiedImage colorFromValue:pixel.
                        oldColorMap := image colorMap.

                        (oldColorMap detect: [:clr| clr = pastedColor] ifNone: nil) isNil
                        ifTrue:[        
                            oldColorMap size < (1 bitShift:image depth) ifTrue:[
                                "/ add to colormap
                                newColorMap isNil ifTrue:[
                                    newColorMap := oldColorMap asOrderedCollection.
                                ].
                                newColorMap add:pastedColor.
        "/                        Transcript showCR:'adding color:' , pastedColor displayString , ' to targets colorMap'.
                            ] ifFalse:[
        "/                        Transcript showCR:'color:' , pastedColor displayString , ' not found in targets colorMap'.
"/                                copiedImage colorMap notNil ifTrue:[
"/                                    copiedImage colorMap at: pixel+1 put: Color black.
"/                                ].
                                anyColorMissing := true.
                            ]
                        ]
                    ].
                ].
                anyColorMissing ifTrue:[
                    answer := Dialog
                                confirmWithCancel:'Some color(s) cannot be represented (colorMap full).\Use nearest or compute colorMap ?' withCRs 
                                labels:#( 'Cancel' 'New ColorMap' 'Use Nearest' )
                                values:#(  nil new nearest)
                                default:3.

                    answer isNil ifTrue:[^ self].

                    currentColorMap := image colorMap.
                    imgX := imagePoint x.
                    imgY := imagePoint y.

                    answer == #nearest ifTrue:[
                        0 to:copiedImage height-1 do:[:y |
                            0 to:copiedImage width-1 do:[:x |
                                |clr n_clr|

                                (copiedImage maskAtX:x y:y) == 0 ifTrue:[
                                    image mask isNil ifTrue:[
                                        image createMask.
                                    ].
                                    image maskAtX:imgX+x y:imgY+y put:0.
                                ] ifFalse:[
                                    clr := copiedImage atX:x y:y.
                                    n_clr := clr nearestIn:currentColorMap.
                                    image atX:imgX+x y:imgY+y put:n_clr
                                ]
                            ]
                        ].
                        image restored.
                        self redraw: (imageBox := (imagePoint * magnification extent: (Clipboard extent * magnification)) expandedBy: 1@1).
                        modified := true.
                        ^ self.
                    ].
                    answer == #new ifTrue:[
                        existingColors := image usedValues asIdentitySet.
                        newColors := copiedImage usedValues.
                        allColors := existingColors addAll:newColors.
                        allColors size > (1 bitShift:image depth) ifTrue:[
                            self warn:'Sorry: too many colors - unimplemented function'.
                            self undo.
                            ^ self.
                        ].

                        newColormap := OrderedCollection new.
                        newColormap addAll:image usedColors.
                        newColormap addAll:copiedImage usedColors.
                        "/ translate image to use new colorMap...

                        "/ translate image to use new colors ...
                        0 to:image height-1 do:[:y |
                            0 to:image width-1 do:[:x |
                                |clr n_idx|

                                (image maskAtX:x y:y) == 1 ifTrue:[
                                    clr := image atX:x y:y.
                                    n_idx := newColormap indexOf:clr.
                                    image pixelAtX:x y:y put:n_idx-1.
                                ]
                            ]
                        ].
                        image colorMap:newColormap.
                        currentColorMap := newColormap.    

                        "/ paste new image...    
                        0 to:copiedImage height-1 do:[:y |
                            0 to:copiedImage width-1 do:[:x |
                                |clr idx|

                                (copiedImage maskAtX:x y:y) == 1
                                ifTrue:[
                                    clr := copiedImage atX:x y:y.
                                    idx := currentColorMap indexOf:clr.
                                    idx == 0 ifTrue:[
                                        currentColorMap add:clr.
                                        idx := currentColorMap size.
                                        idx > (1 bitShift:image depth) ifTrue:[
                                            self warn:'Sorry: too many colors'.
                                            self undo.
                                            ^ self.
                                        ].
                                    ].
                                    image pixelAtX:imgX+x y:imgY+y put:idx-1.
                                    image maskAtX:imgX+x y:imgY+y put:1.
                                ]
                            ]
                        ].
                        image restored.
                        self redraw: (imageBox := (imagePoint * magnification extent: (Clipboard extent * magnification)) expandedBy: 1@1).
                        modified := true.
                        ^ self.
                    ].
                    self warn:'Sorry: unimplemented function'.
                    self undo.
                    ^ self.
                ].
                newColorMap notNil ifTrue:[
                    image colorMap:(MappedPalette withColors:newColorMap).
                ].
            ].

            copiedImage := image class fromImage: copiedImage.
            (newColorMap isNil 
            and:[modeSymbol isNil
            and:[copiedImage mask isNil] ]) ifTrue:[
                "/ use images copy functionality
                "/ however, this copies the mask as well,
                "/ which is not useful here
                image copyFrom: copiedImage x:0 y:0 toX: imagePoint x y: imagePoint y width: copiedImage width height: copiedImage height.
            ] ifFalse:[

                imgX := imagePoint x.
                imgY := imagePoint y.

                0 to:copiedImage height-1 do:[:y |
                    0 to:copiedImage width-1 do:[:x |
                        |wasMasked newMasked dstX dstY oldColor|

                        dstX := imgX + x.
                        dstY := imgY + y.
                        wasMasked := (image maskAtX:dstX y:dstY) == 0.
                        newMasked := (copiedImage maskAtX:x y:y) == 0.

                        "/ with modeUnder, 
                        "/ only replace, if its either unmasked,
                        "/ or the current drawing color.
                        (modeSymbol isNil
                        or:[wasMasked
                        or:[modeSymbol == #withMask]])
                        ifTrue:[
                            newMasked ifFalse:[
                                image 
                                    colorAtX:dstX y:dstY put:(copiedImage colorAtX:x y:y).
                                wasMasked ifTrue:[
                                    image maskAtX:dstX y:dstY put:1
                                ].
                            ] ifTrue:[
                                wasMasked ifFalse:[
                                    modeSymbol == #withMask ifTrue:[
                                        image maskAtX:dstX y:dstY put:0
                                    ]
                                ]
                            ].
                        ].

                    ]
                ].
            ].
            image restored.
            self redraw: (imageBox := (imagePoint * magnification extent: (Clipboard extent * magnification)) expandedBy: 1@1).
"/            masterApplication imagePreView redraw: (imageBox expandedBy: 1).
            modified := true
        ]
   ]

    "Modified: / 18.5.1999 / 20:40:37 / cg"
!

pasteUnderAt: aPoint
    "pasteUnder the image in the clipboard at aPoint.
     In this mode, only pixels which are not equal to
     the current color or masked are pasted."

    self pasteAt:aPoint mode:#under.
!

pasteWithMaskAt: aPoint
    "paste the image in the clipboard at aPoint.
     In this mode, both the mask and the image pixel are pasted"


    self pasteAt:aPoint mode:#withMask.
!

performSpecialOperationOn:imageBox withColor:clr
    |operation x0 y0 x1 y1 grey pixelAction requiredColors missingColors answer|

    operation := Dialog 
           choose:'Which Operation:' 
           fromList:#(
                       'slightly brightened'
                       'slightly darkened'
                       'brightened'
                       'darkened'
                       '-'
                       'greyed'
                       'grey pattern'
                       '-'
                       'reversed'
                     ) 
           values:#(slightlyBrightened slightlyDarkened brightened darkened nil greyed greyPattern nil reversed) 
           lines:6
           cancel:nil.

    self invalidate.
    self windowGroup processExposeEvents.

    operation isNil ifTrue:[^ false].

    x0 := imageBox left.
    y0 := imageBox top.
    x1 := imageBox right - 1.
    y1 := imageBox bottom -1 .

    operation == #slightlyBrightened ifTrue:[
        pixelAction := [:x :y :clr | clr slightlyLightened].
    ].
    operation == #slightlyDarkened ifTrue:[
        pixelAction := [:x :y :clr | clr slightlyDarkened].
    ].
    operation == #brightened ifTrue:[
        pixelAction := [:x :y :clr | clr lightened].
    ].
    operation == #darkened ifTrue:[
        pixelAction := [:x :y :clr | clr darkened].
    ].
    operation == #reversed ifTrue:[
        pixelAction := [:x :y :clr | Color red:(100-clr red) green:(100-clr green) blue:(100-clr blue) ].
    ].
    operation == #greyed ifTrue:[
        pixelAction := [:x :y :clr | clr blendWith:Color grey].
    ].
    operation == #greyPattern ifTrue:[
        pixelAction := [:x :y :clr | Color grey].
    ].
    pixelAction isNil ifTrue:[self halt. ^ false].

    "/ compute required colors ...
    requiredColors := Set new.
    self image 
        colorsFromX:x0 y:y0 toX:x1 y:y1 
        do:[:x :y :clr | 
            requiredColors add:(pixelAction value:x value:y value:clr)
        ].

    missingColors := requiredColors select:[:clr | (image colorMap includes:clr) not].

    missingColors notEmpty ifTrue:[
        answer := Dialog
                    confirmWithCancel:'Some color(s) cannot be represented in the images colorMap.\Use nearest or compute colorMap ?' withCRs 
                    labels:#( 'Cancel' 'Add to ColorMap'  'Use Nearest')
                    values:#( nil add nearest)
                    default:3.
        answer isNil ifTrue:[^ self].
        answer == #add ifTrue:[
            self halt:'this function is not yet implemented'.
            missingColors do:[:eachColor |
            ].
            ^ false.
        ].
    ].

    "/ now, do it
    self image 
        colorsFromX:x0 y:y0 toX:x1 y:y1 
        do:[:x :y :clr |
            |newClr|

            newClr := pixelAction value:x value:y value:clr.
            answer == #nearest ifTrue:[
                newClr := newClr nearestIn:image colorMap
            ].
            self image colorAtX:x y:y put:newClr
        ].

    ^ true.
!

pointAt:aPoint
    "draw a single pixel with the currently selected color"

    |imagePoint clr pix|

    imagePoint := aPoint // magnification.
    (clr := self selectedColor) isNil ifTrue:[
        pix := self selectedColorIndex
    ].

    pix notNil ifTrue:[
        image colorMap atImageAndMask:imagePoint putValue:pix.
        modified := true.
    ] ifFalse:[     
        "/ clr notNil ifTrue:[
            image atImageAndMask:imagePoint put:clr.
            modified := true.
        "/ ]
    ].
    self invalidate:((imagePoint * magnification extent: magnification) expandedBy: 1).

    "Modified: / 5.9.1998 / 13:25:29 / cg"
!

reduceColorResolutionBy:numBits
    |xMax yMax r g b n_r n_g n_b clr pix map revMap n_clr n_pix mask anyChange
     newColors newColorArray newImage|

    numBits > 7 ifTrue:[
        self warn:'Max. number of bits to strip off is 7.'.
        ^ false
    ].
    mask := (16rFF bitShift:numBits) bitAnd:16rFF.

    anyChange := false.

    newColors := Set new.
    newColorArray := OrderedCollection new.
    map := Array new:256.
    revMap := OrderedCollection new.

    newImage := image class width:image width height:image height depth:image depth.
    newImage photometric:image photometric.
    newImage colorMap:(image colorMap copy).
    newImage bits:(image bits copy).
    newImage mask:(image mask copy).

    xMax := image width - 1.
    yMax := image height - 1.

    image photometric == #palette ifFalse:[
        "/ direct manipulation of the pixels
        0 to:yMax do:[:y |
            0 to:xMax do:[:x |
                pix := image pixelAtX:x y:y.
                r := image redBitsOf:pix.
                g := image greenBitsOf:pix.
                b := image blueBitsOf:pix.
                n_r := r bitAnd:mask.
                n_g := g bitAnd:mask.
                n_b := b bitAnd:mask.
                n_pix := image valueFromRedBits:n_r greenBits:n_g blueBits:n_b.
                n_pix ~= pix ifTrue:[
                    newImage pixelAtX:x y:y put:n_pix.
                    anyChange := true.
                ]
            ]
        ].
        anyChange ifFalse:[
            ^ false
        ].
    ] ifTrue:[
        "/ manipulate the colormap
        0 to:yMax do:[:y |
            0 to:xMax do:[:x |
                pix := image pixelAtX:x y:y.
                (n_pix := map at:pix+1) isNil ifTrue:[
                    clr := image colorAtX:x y:y.
                    r := clr redByte.
                    g := clr greenByte.
                    b := clr blueByte.
                    n_r := r bitAnd:mask.
                    n_g := g bitAnd:mask.
                    n_b := b bitAnd:mask.
                    n_clr := Color redByte:n_r greenByte:n_g blueByte:n_b.
                    (newColors includes:n_clr) ifFalse:[
                        newColors add:n_clr.
                        newColorArray add:n_clr.
                        revMap add:pix.
                        map at:pix+1 put:(n_pix := revMap size - 1).
                    ] ifTrue:[
                        "/ mhmh - multiple pixels mapped to the same color
                        n_pix := (newColorArray indexOf:n_clr) - 1.
                        map at:pix+1 put:n_pix.
                    ]
                ].
                newImage pixelAtX:x y:y put:n_pix.
            ]
        ].
        revMap size == image colorMap size ifTrue:[
            revMap = (0 to:revMap size-1) ifTrue:[
                ^ false
            ]
        ].

        newImage colorMap:(MappedPalette withColors:newColorArray).
    ].

    self makeUndo.
    self image:newImage.
    ^ true
!

resizeImageTo:newSize

    |newImage newMaskImage|

    newImage := image class width: newSize x height: newSize y depth: image depth.
    newImage photometric:image photometric.
    newImage colorMap:image colorMap copy.
    newImage bits: (ByteArray new: newImage bytesPerRow * newSize y).

    image mask notNil ifTrue:[
        newMaskImage := Depth1Image width: newSize x height: newSize y.
        newMaskImage photometric: image mask photometric.
        newMaskImage colorMap: image mask colorMap copy.
        newMaskImage bits:(ByteArray new: newMaskImage bytesPerRow * newSize y).
        newImage mask: newMaskImage
    ].

    newImage copyFrom:image x:0 y:0 toX:0 y:0 width: (image width min:newSize x) height: (image height min:newSize y).
    self makeUndo.
    self image: newImage.
!

rotateImageBy:rotation
    "rotate by (degrees)"

    Object errorSignal handle:[:ex|
        self warn: 'Image rotation failed!!\' withCRs, 'Increaing the image depth could help.'
    ] do:[   
        self makeUndo.
        self image: (image hardRotated: rotation)
    ]

    "Modified: / 29.7.1998 / 18:21:14 / cg"
!

shiftImageHorizontal:shiftH vertical:shiftV
    self shiftImageHorizontal:shiftH vertical:shiftV wrap:false
!

shiftImageHorizontal:shiftH vertical:shiftV wrap:doWrap
    "shift the pixels; 
     shift<0 is left-shift/up-shift; shift>0 is right-shift/down-shift;
     doWrap controls if shifted-out pixels are to be shifted in at the opposite side.
     i.e.:
        0123456789 -> 3456789789 (shift: -3)    0123456789 -> 0120123456 (shift:3)
     or, with wrap:
        0123456789 -> 3456789012 (shift: -3)    0123456789 -> 7890123456 (shift:3)
    "

    |newImage|

    newImage := self shifted:image horizontal:shiftH vertical:shiftV wrap:doWrap.
    self image:newImage.
!

shifted:image horizontal:shiftH vertical:shiftV wrap:doWrap
    "shift the pixels; 
     shift<0 is left-shift/up-shift; shift>0 is right-shift/down-shift;
     doWrap controls if shifted-out pixels are to be shifted in at the opposite side.
     i.e.:
        0123456789 -> 3456789789 (shift: -3)    0123456789 -> 0120123456 (shift:3)
     or, with wrap:
        0123456789 -> 3456789012 (shift: -3)    0123456789 -> 7890123456 (shift:3)
    "

    |w h srcX srcY dstX dstY newImage|

    doWrap ifTrue:[
        "/ if wrapping, split into two operations to make wrap-code below simpler.

        shiftH ~~ 0 ifTrue:[
            shiftV ~~ 0 ifTrue:[
                newImage := self shifted:image    horizontal:shiftH vertical:0 wrap:doWrap.
                newImage := self shifted:newImage horizontal:0      vertical:shiftV wrap:doWrap.
                ^ newImage
            ].
        ].
    ].
    (shiftV == 0 and:[shiftH == 0]) ifTrue:[
        ^ image
    ].

    w := image width.
    h := image height.

    newImage := image copy.

    srcX := srcY := dstX := dstY := 0.
    shiftH < 0 ifTrue:[
        srcX := shiftH negated
    ] ifFalse:[
        dstX := shiftH
    ].
    shiftV < 0 ifTrue:[
        srcY := shiftV negated
    ] ifFalse:[
        dstY := shiftV
    ].

    newImage copyFrom:image x:srcX y:srcY toX:dstX y:dstY width:w-shiftH abs height:h-shiftV abs.

    doWrap ifTrue:[
        srcX := srcY := dstX := dstY := 0.

        "/ already simplified - see above
        shiftH ~~ 0 ifTrue:[
            "/ shiftV known to be 0
            shiftH < 0 ifTrue:[
                dstX := w-1-shiftH negated
            ] ifFalse:[
                srcX := w-1-shiftH
            ].
            w := shiftH abs.
        ] ifFalse:[
            "/ shiftH known to be 0
            shiftV < 0 ifTrue:[
                dstY := h-1-shiftV negated
            ] ifFalse:[
                srcY := h-1-shiftV
            ].
            h := shiftV abs.
        ].
        newImage copyFrom:image x:srcX y:srcY toX:dstX y:dstY width:w height:h.
        ^ newImage
    ].

    ^ newImage.

    "Created: / 7.9.1998 / 13:00:16 / cg"
    "Modified: / 7.9.1998 / 14:15:32 / cg"
!

specialOperationAt: aPoint
    "special operation on a rectangular area"

    |choosedBox imageBox clr|

    choosedBox := self dragRectangleStartingAt: aPoint emphasis: #filledBox.
    imageBox := choosedBox origin//magnification extent: (choosedBox extent//magnification).

    (self performSpecialOperationOn:imageBox withColor:self selectedColor) ifFalse:[
        ^ self
    ].

    image restored.
    self invalidate. "/ : (choosedBox expandedBy: 1).

    "/ self redraw: (choosedBox expandedBy: 1).

"/        "/ cg: what a kludge - please change to use a valueHolder,
"/        "/ which gets the information ...
"/        masterApplication imagePreView redraw: (imageBox expandedBy: 1).

        "/ cg: still a kludge - but less ugly
    self changed:#subImageIn with:(imageBox expandedBy: 1).

    modified := true
!

undo

    undoImages notEmpty ifTrue:[           
        windowGroup withExecuteCursorDo:[
            modified := false. 
            self image: undoImages removeLast.
"/            "/ cg: what a kludge - please change to use a valueHolder,
"/            masterApplication notNil ifTrue:[
"/                masterApplication listOfColors contents: image colorMap.
"/                masterApplication findColorMapMode.
"/"/                undoImages isEmpty ifTrue: [
"/"/                    masterApplication valueOfCanUndo value: false
"/"/                ].
"/            ].
            self changed:#image.

            "/ cg: not needed - image: already does it.
"/            self invalidate
        ]
    ]

    "Modified: / 10.2.2000 / 23:21:24 / cg"
! !

!ImageEditView methodsFor:'image setting'!

image:anImage
    |retVal fileName|

    anImage isImage ifTrue:[           
        (image isNil or: [self checkModified]) ifTrue: [
"/ cg: that is too ugly ...
"/            masterApplication notNil ifTrue: [
"/"/                undoImages notEmpty ifTrue: [
"/"/                    masterApplication valueOfCanUndo value: true
"/"/                ].
"/                masterApplication imagePreView image: anImage
"/            ].
            image notNil ifTrue: [
                fileName := image fileName.
                anImage fileName isNil ifTrue: [anImage fileName: fileName].
            ].
            super image: anImage.
            retVal := self.
        ].
    ] ifFalse: [
        super image: nil.
    ].
    "/cg: still a kludge, but less ugly
    self changed:#image.

    self updateImageInfo: self imageInfoString. 
    ^ retVal

    "Modified: / 10.2.2000 / 23:33:12 / cg"
!

loadFromFile: aFileName

    aFileName isNil ifTrue: [^nil].

    Object errorSignal handle:[:exeption|
        modified := false.
        self warn: exeption errorString.
        ^nil
    ] do:[ 
        |imageFromFile|
        (imageFromFile := Image fromFile: aFileName) notNil
        ifTrue:[
            self releaseUndos.
            self image: imageFromFile. 
            imageReaderClass := ImageReader allSubclasses
                detect: [:cls| cls isValidImageFile: aFileName asFilename pathName]
                ifNone: [self error: 'Unknown image file format!!']
        ] ifFalse:[
            self error: 'Not an image file (or unrecognized format) !!'
        ]
    ]

    "Modified: / 29.7.1998 / 18:09:13 / cg"
!

loadFromMessage: aMessage

    (self resourceMessage: aMessage) isNil ifTrue:[
        ^ nil
    ].

    ^self loadfromClass: resourceClass andSelector: resourceSelector

   
!

loadfromClass: aClassOrSymbol andSelector: aStringOrSymbol

    |aClass| 

    imageReaderClass := nil.
    self resourceClass: aClassOrSymbol.
    self resourceSelector: aStringOrSymbol.

    (aClass := Smalltalk at: resourceClass) isClass ifTrue:[ 
        (aClass class implements: resourceSelector)
        ifTrue:
        [ 
            self releaseUndos.
            ^self image: (aClass perform: resourceSelector) copy
        ].
        (aClass implements: resourceSelector)
        ifTrue:
        [ 
            self releaseUndos.
            ^self image: (aClass basicNew perform: resourceSelector) copy
        ].
    ].
    modified := false.
    ^ nil

! !

!ImageEditView methodsFor:'initialize / release'!

destroy
    ClipboardMagnified := Clipboard := nil.
    LastMagnification      := magnification.

    super destroy
!

initialize

    super initialize.

    self enableMotionEvents.

    undoImages        := List new: MaxUndos.
    magnification     := LastMagnification ? (8@8).
    modified          := false.
    mouseKeyColorMode := 1.
    resourceClass     := resourceSelector := ''.
    drawingColorHolders := Array with:(nil asValue) with:(nil asValue).   "/ left/right mouse colors
    drawingPixelHolders := Array with:(nil asValue) with:(nil asValue).   "/ left/right mouse colors
    editMode          := #point.
! !

!ImageEditView methodsFor:'printing & storing'!

askForFileNameToSave:msg
    "ask for a fileName"

    |lastFn fn filters|

    filters := FileSelectionBrowser saveImageFileNameFilters.
    lastFn := self image fileName.
    lastFn isNil ifTrue:[
        fn := FileSelectionBrowser
                request: msg
                inDirectory: LastSaveDirectory
                withFileFilters: filters
    ] ifFalse:[
        fn := FileSelectionBrowser
                request: msg
                fileName: lastFn
                withFileFilters: filters
    ].

    ^ fn
!

loadFromClass

    ^self loadFromMessage: 
        (ResourceSelectionBrowser
            request: 'Load Image From Class'
            onSuperclass: nil
            andClass: self resourceClass
            andSelector: self resourceSelector
            withResourceTypes: #(image fileImage programImage))
            

!

makeUndo

    image notNil ifTrue:[       
        undoImages size >= MaxUndos ifTrue:[
            undoImages removeFirst.
        ].
        undoImages add: image copy
    ]
!

print

    image notNil 
    ifTrue: 
    [
	|stream|
	Printer supportsPostscript ifFalse:
	[
	    ^self warn:'No postscript printer detected!!'
	].
	stream := Printer newNative.
	stream isNil ifTrue:
	[
	    ^self warn:'Cannot open printer stream!!'
	].
	self withWaitCursorDo:
	[
	    |psgc|
	    psgc := PSGraphicsContext on:stream.  
	    psgc displayForm: (image magnifiedBy: magnification) x:0 y:0.
	    psgc close
	]
    ]
!

save

    self saveImageOrMask: #image.

!

save:image imageOrMask:what
    "save the image or the mask only (if what == #mask)"

    image isNil ifTrue:[
        Dialog warn: 'No image to save!!'.
        ^ self.
    ].
    self save:image imageOrMask:what as:image fileName.
!

save:image imageOrMask:what as:fileNameArg
    "save the image or the mask only (if what == #mask)"

    |fileName fileNameString|

    fileName := fileNameArg asFilename.

    Object errorSignal handle:[:ex|
        |msg|

        ex signal == Image fileCreationErrorSignal ifTrue:[
            msg := resources string:'Cannot create file: ''%1''' with:fileName asFilename pathName allBold
        ] ifFalse:[
            msg := ex errorString.
        ].
        Dialog warn:msg.
    ] do:[   
        Image informationLostQuerySignal handle:[:ex|
            "/ should make those warnings visible ...
            (self confirm:(ex errorString , '\\Save anyway ?') withCRs) ifTrue:[
                ex proceed.
            ]
        ] do:[   
            windowGroup withCursor:Cursor write do:[
                |suff fn|

                image isNil ifTrue:[
                    ^ self error: 'No image to save!!'
                ].

                what = #mask ifTrue:[   
                    image mask isNil ifTrue: [^self error: 'No image mask to save!!'].
                ].

                fileName name size = 0 ifTrue: [^self error: 'No file name detected!!'].
                suff := fileName suffix asLowercase.
                imageReaderClass := nil.
                imageReaderClass := MIMETypes imageReaderForSuffix:suff.
"/                (suff = 'tiff' or:[suff = 'tif']) ifTrue: [
"/                    imageReaderClass := TIFFReader
"/                ] ifFalse:[
"/                    suff = 'xpm' ifTrue: [
"/                        imageReaderClass := XPMReader
"/                    ] ifFalse:[
"/                        suff = 'xbm' ifTrue: [
"/                            imageReaderClass := XBMReader
"/                        ] ifFalse:[
"/                            suff = 'gif' ifTrue: [
"/                                imageReaderClass := GIFReader
"/                            ] ifFalse:[
"/                                (suff = 'jpg' or:[suff = 'jpeg']) ifTrue: [
"/                                    imageReaderClass := JPEGReader
"/                                ].
"/                            ]
"/                        ]
"/                    ]
"/                ].

                imageReaderClass isNil ifTrue: [
                    imageReaderClass := XPMReader. 
                    fileNameString := fileName, '.xpm'.
                    fileName := fileNameString asFilename.
                    image fileName:fileNameString.
                    Dialog warn:(('Dont know how to write ''.' , suff , '''-files\\Saving in xpm format as ''%1''.') 
                                withCRs bindWith:fileNameString allBold).
                ].
                (imageReaderClass canRepresent:image) ifFalse:[
                    imageReaderClass == XPMReader ifTrue:[
                        Dialog warn:('Saving in ''.' , suff , '''-format is not supported (or image cannot be represented in this format).\\Please try another format.') withCRs.
                        ^ self.
                    ].
                    imageReaderClass := XPMReader. 
                    fileNameString := fileName, '.xpm'.
                    fileName := fileNameString asFilename.
                    image fileName:fileNameString.
                    Dialog warn:(('Saving in ''.' , suff , '''-format is not supported (or image cannot be represented in this format).\\Saving in xpm format as ''%1''.') 
                                withCRs bindWith:fileNameString allBold).
                ].
                Transcript showCR:('saving as:' , fileName pathName).

                what = #image ifTrue: [ image saveOn:fileName using: imageReaderClass. modified := false].
                what = #mask ifTrue: [image mask saveOn:fileName using: imageReaderClass].

                LastSaveDirectory := fileName directoryName.
                fileName exists ifFalse:[
                    Dialog warn:'Oops image save failed.'
                ]
            ]   
        ]
    ]

    "Modified: / 18.5.1999 / 19:46:54 / cg"
!

saveAs

    self saveImageFileAs
!

saveButtonImageToFileAs
    |fn|

    fn := self askForFileNameToSave:'Save Button Image to File'.
    self saveButtonImageToFileAs:fn

    "Modified: / 30.9.1998 / 23:04:11 / cg"
!

saveButtonImageToFileAs: aFileName
    "save the image as if in a button in aFileName"

    |button grabbedImage|

    aFileName isNil ifTrue: [^nil].

    image isNil ifTrue:[
        self warn: 'No image or image mask detected!!'.
        ^ self.
    ].

    button := Button label:image.
    button openAt:5@5.
    button waitUntilVisible.

    grabbedImage := Image fromView:button.
    button destroy.

    self save:grabbedImage imageOrMask:#image as:aFileName

    "/ self saveImageOrMask: #mask
!

saveImageFileAs
    "ask for a fileName and save the image"

    |fn|

    fn := self askForFileNameToSave:'Save Image To File'.
    self saveImageFileAs:fn
!

saveImageFileAs: aFileName
    "save the image in aFileName"

    aFileName isNil ifTrue: [^nil].
    image notNil ifTrue:[
        self save:image imageOrMask:#image as:aFileName.
    ] ifFalse:[
        self warn: 'No image for saving!!'
    ]

    "Modified: / 30.9.1998 / 23:04:55 / cg"
!

saveImageMaskFileAs
    "ask for a fileName and save the mask only"

    |fn|

    fn := self askForFileNameToSave:'Save Image Mask To File'.
    self saveImageMaskFileAs:fn

    "Modified: / 30.9.1998 / 23:04:11 / cg"
!

saveImageMaskFileAs: aFileName
    "save the mask only in aFileName"

    aFileName isNil ifTrue: [^nil].
    (image notNil and:[image mask notNil]) ifTrue:[
        self save:image imageOrMask:#mask as:aFileName.
    ] ifFalse:[
        self warn: 'No image or image mask detected!!'
    ]

    "Modified: / 30.9.1998 / 23:06:24 / cg"
!

saveImageOrMask:what
    "save the image or the mask only (if what == #mask)"

    self save:image imageOrMask: what
!

saveMethod
    Object errorSignal handle:[:ex|
        self warn: ex errorString.
        ^nil                                 
    ] do: [   
        |category imageStoreStream cls sel mthd imageKey|

        windowGroup withExecuteCursorDo:[
            (self resourceSelector trimBlanks size = 0) | (cls := Smalltalk at: self resourceClass asSymbol) isClass not 
                ifTrue: [^self saveMethodAs].

            CodeGeneratorTool
                createImageSpecMethodFor:self image 
                comment:(ResourceSpecEditor codeGenerationCommentForClass: ImageEditor) 
                in:cls class 
                selector:self resourceSelector.

            "/ flush cache images in the Icon class (kludge)
            Icon flushCachedIcons.
            modified := false.

            LastSaveClass := cls theNonMetaclass name.
        ]
    ]

    "Modified: / 31.7.1998 / 20:12:54 / cg"
!

saveMethodAs
    |className|

    className := self resourceClass.
    className size == 0 ifTrue:[
        className := LastSaveClass
    ].

    (self resourceMessage:
        (ResourceSelectionBrowser
            request: 'Save Image In Class'
            onSuperclass: #Object
            andClass: className
            andSelector: self resourceSelector
            withResourceTypes: #(image fileImage))) notNil
    ifTrue: [   
        ^ self saveMethod
    ].  
    ^nil
! !

!ImageEditView methodsFor:'queries'!

heightOfContents

    image isNil ifTrue:[^0].
    ^(image height * magnification y) rounded
!

imageContainsPastePoint: aPoint

    ^image notNil and: 
	[Clipboard notNil and:
	[((0@0 corner:(image extent) "- 1" - Clipboard extent) containsPoint: (((aPoint - margin + 1) / magnification) floor))]]
!

imageContainsPoint: aPoint

    ^image notNil and:
	[((0@0 corner:(image extent) - 1) containsPoint: (((aPoint - margin + 1) / magnification) floor))]
!

imageInfoString

    |imageInfoString usedColors|

    image isNil ifTrue: [imageInfoString := 'No image loaded.'] 
    ifFalse: [
	image colorMap isNil ifTrue: [usedColors := '?'] ifFalse: [usedColors := image usedColors size].
	imageInfoString := image width printString, 'x'
	    , image height printString, 'x'
	    , (2 raisedTo: image depth) printString
	    , (image mask notNil ifTrue: [' (mask + '] ifFalse: ['('])
	    , usedColors printString
	    , ' used colors)'].

    ^imageInfoString
!

widthOfContents

    image isNil ifTrue:[^0].
    ^(image width * magnification x) rounded
! !

!ImageEditView methodsFor:'release'!

releasePasteDrawing

    self repairDamage.
    (lastPastePoint notNil and: [ClipboardMagnified notNil]) 
    ifTrue: 
    [ 
        self redraw: ((lastPastePoint"-self viewOrigin") extent: (ClipboardMagnified extent)). 
        "/ self repairDamage.
    ].
    lastPastePoint := ClipboardMagnified := nil
!

releaseUndos

    undoImages removeAll.
    "/ cg: what a kludge - please change to use a valueHolder,
"/    masterApplication notNil ifTrue:[
"/        masterApplication valueOfCanUndo value: false.
"/    ].

    "Modified: / 31.7.1998 / 02:47:21 / cg"
! !

!ImageEditView methodsFor:'testing'!

checkModified

    modified
    ifTrue:
    [
	((YesNoBox title:(resources string:'Image was modified !!'))
	    noText:(resources string:'Cancel');
	    yesText:(resources string:'Forget it and proceed');
	    showAtPointer;
	    accepted) ifFalse: [^false].
	modified := false
    ].
    ^true

    "Modified: / 29.7.1998 / 18:55:24 / cg"
! !

!ImageEditView class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libwidg2/ImageEditView.st,v 1.180 2003-05-13 17:44:09 cg Exp $'
! !

ImageEditView initialize!