ImgEditV.st
author Claus Gittinger <cg@exept.de>
Wed, 20 Jan 1999 20:26:17 +0100
changeset 1184 58e399d8c312
parent 1180 dcb9dede5128
child 1228 0aae4f7389ca
permissions -rw-r--r--
checkin from browser

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

ImageView subclass:#ImageEditView
	instanceVariableNames:'magnification selectColors imageReaderClass resourceClass
		resourceSelector mouseKeyColorMode undoImages modified
		masterApplication editMode lastPastePoint imageInfoHolder
		activityInfoHolder pickedColorHolder'
	classVariableNames:'Clipboard LastMagnification ClipboardMagnification
		GridMagnification MaxUndos'
	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 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"
!

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.
	ClipboardMagnification := nil.
    ]

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

masterApplication

    ^masterApplication
!

masterApplication: anApplicationModel

    masterApplication := anApplicationModel
!

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
!

selectColors

    ^selectColors
!

selectColors: anArrayTwoColors

    selectColors := anArrayTwoColors
!

selectedColor

   ^selectColors at: mouseKeyColorMode
!

selectedColor: aColor

    selectColors at: mouseKeyColorMode put: aColor
!

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 >= GridMagnification
    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.
    ]



!

fillFramedRectangle: aRectangle

    self fillRectangle: aRectangle.
    self drawFramesIn: aRectangle
!

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

    |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).
                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).
                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 colorAtX:xx y:yy) = Color black ifTrue:
                [
                    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).
        self fillFramedRectangle: (origin extent: runW@magY).
        maskColor ifTrue:
        [
            self xoring: [self fillRectangle: (origin + sizeOfMaskPoint extent: sizeOfMaskPoint)]
        ].
        runW := 0.
    ].

    "Modified: / 8.1.1999 / 22:30:50 / cg"
!

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

    |ih iw xI yI|

    image isNil ifTrue:[^self].

    magnification = (1@1) 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
    ].
    (x + w - 1) > (xI + (magnification x * image width)) ifTrue:
    [
	self clearRectangleX:(xI + (magnification x * image width))
			   y:y
		       width:(x + w - (magnification x * image width) - xI)
		      height:h
    ].
    (y + h - 1) > (yI + (magnification y * image height)) ifTrue:
    [
	self clearRectangleX:margin
			   y:(yI + (magnification y * image height))
		       width:w
		      height:(y + h - (magnification y * image height) - yI)  
    ].
    self drawFrame.
    self clippingRectangle: nil.

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

!ImageEditView methodsFor:'edit modes'!

editMode

    ^editMode
!

editMode: anEditMode

    editMode := anEditMode
!

mouseKeyColorMode

    ^mouseKeyColorMode printString
!

mouseKeyColorMode:aMode

    mouseKeyColorMode := aMode
! !

!ImageEditView methodsFor:'event handling'!

buttonMotion:state x:x y:y
    self drawCursorAt: x@y.
    state ~~ 0 ifTrue: [
	("self selectedColor notNil" true and: [(self imageContainsPoint: x@y) and: [editMode value = #point]])
	    ifTrue: [^self pointAt: x@y]
    ] ifFalse:[
	(editMode = 'paste' or:[editMode = 'pasteUnder']) ifTrue: [
	    ("self selectedColor notNil" true and: [self imageContainsPastePoint: x@y]) 
		ifTrue:  [self drawPasteRectangleAt: x@y]
		ifFalse: [self cursor:Cursor stop. self releasePasteDrawing]
	]
    ]

    "Modified: / 5.9.1998 / 13:28:15 / cg"
!

buttonPress:button x:x y:y

    self drawCursorAt: x@y.
    ("self selectedColor notNil" true and: [self imageContainsPoint: x@y])
    ifTrue:
    [   
	|mouseButtonColorToolBar clr|

	self sensor shiftDown ifTrue:[
	    pickedColorHolder notNil ifTrue:[
		"/ select the color under the cursor, place it into the
		"/ pickedColorHolder/
		clr := image colorAt:((x@y)//magnification).
		pickedColorHolder value:clr
	    ].
	] ifFalse:[
	    "/ cg: what a kludge - please change to use a valueHolder,
	    "/ which gets the information ...

	    mouseKeyColorMode := button.
	    mouseButtonColorToolBar := masterApplication builder componentAt: #MouseButtonColorToolBar.
	    self makeUndo.
	    masterApplication valueOfCanUndo value: true.
	    (mouseButtonColorToolBar itemAt: mouseKeyColorMode) toggleIndication.
	    mouseButtonColorToolBar do: [:i| i updateIndicators].
	    self perform: (editMode, 'At:') asSymbol with: x@y
	]
    ]

    "Modified: / 5.9.1998 / 13:28:02 / cg"
!

buttonRelease:button x:x y:y

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

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

    "Modified: / 5.9.1998 / 13:20:12 / cg"
!

pointerLeave:state

    super pointerLeave: state.

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

    (editMode value = #paste or:[editMode value = #pasteUnder]) ifTrue: [self releasePasteDrawing]

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

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

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

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

    firstPoint := currentPoint := lastCurrentPoint := aPoint//magnification*magnification.
    magnification >= GridMagnification 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 from:device rootView id to:self id.

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

	    currentPoint := (0@0) max: (image extent * magnification min: (p :=  self translation negated + 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: / 21.8.1998 / 20:34:42 / cg"
!

drawCursorAt: aPoint
    |clr|

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

    (aPoint x < (image width * magnification) 
    and:[aPoint y < (image height * magnification)
    and:[aPoint x >= 0
    and:[aPoint y >= 0]]])
    ifFalse:[
	self updateImageInfo: self imageInfoString. 
	self cursor:Cursor stop.
    ] ifTrue: [
	clr := image colorAt:aPoint//magnification.
	self updateImageInfo: (aPoint//magnification) printString 
			, ' (red:' 
			, clr redByte printString
			, ' green:' , clr greenByte printString
			, ' blue:' , clr blueByte 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 rectangle: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).
	modified := true
    ].

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

changeGridMagnification

    |box newGridMagnification|
    box := EnterBox new.
    box title:'Grid Magnification:'.
    box okText:'OK'.
    box abortText:'Cancel'.
    box initialText:GridMagnification x printString.
    box showAtPointer.
    (box accepted and: [(newGridMagnification := Number readFromString: box contents onError:[2]) notNil])
    ifTrue:
    [
	GridMagnification := (99 min: (2 max: newGridMagnification)) asPoint.
	self invalidate
    ]
!

copyAt: aPoint

    |choosedBox|

    choosedBox := self dragRectangleStartingAt: aPoint emphasis: #inverseFilledBox.
    ClipboardMagnification := nil.
    Clipboard := image subImageIn: (choosedBox origin//magnification extent: (choosedBox extent//magnification)).
    self redraw: (choosedBox expandedBy: 1)

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

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

drawPasteRectangleAt: aPoint

    |currentPoint gridCorrection extent|

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

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

	extent       := ClipboardMagnification extent.

	currentPoint := currentPoint - self viewOrigin.

	self redraw: ((lastPastePoint ? currentPoint) extent: extent).

	(extent x > 200 or: [extent y > 200])
	ifTrue:
	[
	    self xoring: [self fillRectangle: (currentPoint extent: extent)]   
	]
	ifFalse:
	[
	    self displayDeviceForm: ClipboardMagnification x: currentPoint x y: currentPoint y
	]  
    ]. 
    lastPastePoint := currentPoint.

    "Modified: / 29.7.1998 / 02:18:11 / 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 ...'.
	    [
		filledPoints := image floodFillAt: aPoint//magnification withColor:clr.
		image restored.

		"/ animation effect ...    
		filledPoints size < 300
		ifTrue: [
		    filledPoints do: [:p| self redraw: ((p * magnification extent: magnification) expandedBy: 1)]
		] ifFalse: [
		    self invalidate
		].
		"/ cg: what a kludge - please change to use a valueHolder,
		"/ which gets the information ...
		masterApplication imagePreView invalidate.
		modified := true
	    ] valueOnUnwindDo:[
		self updateActivity:'Flood fill aborted.'
	    ].
	].
	self updateActivity:''
    ]

    "Modified: / 5.9.1998 / 13:28:24 / 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).
	modified := true
    ]

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

flipHorizontal

    self makeUndo.
    self image: image copy flipHorizontal

!

flipVertical

    self makeUndo.
    self image: image copy flipVertical

!

magnifyImage

    |box newSize|
    box := EnterBox new.
    box title:'Image new size:'.
    box okText:'OK'.
    box abortText:'Cancel'.
    box initialText:image extent printString.
    box showAtPointer.
    (box accepted and: [(newSize := Object readFromString: box contents onError:nil) notNil])
    ifTrue:
    [
	self makeUndo.
	self image: (image magnifiedBy: newSize/image extent)
    ]
!

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 makeUndo.
    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 negative
!

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

    self pasteAt:aPoint modeUnder:false.
!

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

    ClipboardMagnification isNil ifTrue: [^self].

    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 imagePoint imgX imgY copiedImage imageBox presentClr newColorMap|


	    choosedBox := self dragRectangleStartingAt: aPoint emphasis: #inverseFilledBox.

	    imagePoint := choosedBox origin//magnification.

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

		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 at: pixel+1 put: Color black
			]
		    ]
		].

		newColorMap notNil ifTrue:[
		    image colorMap:(Colormap fromColors:newColorMap).
		].
	    ].

	    copiedImage := image class fromImage: copiedImage.
	    (newColorMap isNil and:[modeUnder not]) ifTrue:[
		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.
			(modeUnder not
			or:[wasMasked
			or:[(oldColor := image colorAtX:dstX y:dstY) = (selectColors at:1)]])
			ifTrue:[
			    image 
				colorAtX:dstX
				       y:dstY
				     put:(copiedImage colorAtX:x y:y).
			    (wasMasked and:[newMasked not]) ifTrue:[
				image mask pixelAtX:dstX y:dstY put:1
			    ].
			]
		    ]
		].
	    ].
	    image restored.
	    self redraw: (imageBox := (imagePoint * magnification extent: (Clipboard extent * magnification)) expandedBy: 1@1).
"/            masterApplication imagePreView redraw: (imageBox expandedBy: 1).
	    modified := true
	]
   ]

    "Modified: / 5.9.1998 / 13:36:58 / 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 modeUnder:true.
!

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

    |imagePoint imageBox clr|

    (clr := self selectedColor) notNil ifTrue:[
	imagePoint := aPoint//magnification.
	image atImageAndMask:imagePoint put:clr.
	self redraw:(imageBox := (imagePoint * magnification extent: magnification) expandedBy: 1).
	modified := true.
    ]

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

resizeImage

    |box newSize|
    box := EnterBox new.
    box title:'Image new size:'.
    box okText:'OK'.
    box abortText:'Cancel'.
    box initialText:image extent printString.
    box showAtPointer.
    (box accepted and: [(newSize := Object readFromString: box contents onError:nil) notNil])
    ifTrue:
    [
	|newImage|
	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|
	    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.
    ]
!

rotateImage

    |box rotation|
    box := EnterBox new.
    box title:'Rotate by (degrees, clockwise):'.
    box okText:'OK'.
    box abortText:'Cancel'.
    box initialText: '0'.
    box showAtPointer.
    (box accepted and: [(rotation := Object readFromString: box contents onError:nil) notNil])
    ifTrue:
    [   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"
!

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].
	    ].
	    "/ cg: not needed - image: already does it.
"/            self invalidate
	]
    ]

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

!ImageEditView methodsFor:'image setting'!

image:anImage
    |retVal|

    anImage isImage
    ifTrue:
    [           
	(image isNil or: [self checkModified])
	ifTrue:
	[
	    |fileName|
	    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.
    ].

    self updateImageInfo: self imageInfoString. 
    ^ retVal

    "Modified: / 29.7.1998 / 18:27:31 / 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]
		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 and: 
    [aClass class implements: resourceSelector])
    ifTrue:
    [ 
	self releaseUndos.
	^self image: (aClass perform: resourceSelector) copy
    ]
    ifFalse:
    [
	modified := false.
	^nil
    ]

! !

!ImageEditView methodsFor:'initialization'!

initialize

    super initialize.

    self enableMotionEvents.

    GridMagnification := GridMagnification ? (8@8).
    MaxUndos          := MaxUndos ? 3.
    undoImages        := OrderedCollection new: MaxUndos.
    magnification     := LastMagnification ? GridMagnification.
    modified          := false.
    mouseKeyColorMode := 1.
    resourceClass     := resourceSelector := ''.
    selectColors      := Array with: nil with: nil.
    editMode          := #point.

! !

!ImageEditView methodsFor:'printing & storing'!

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:
    [       
	MaxUndos <= undoImages size
	    ifTrue:  [undoImages contents: (undoImages copyFrom: 2 to: MaxUndos)].
	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.

!

saveAs

    self saveImageFileAs
!

saveImageFileAs
    "ask for a fileName and save the image"

    self saveImageFileAs:
        (FileSelectionBrowser
            request: 'Save Image To File'
            fileName: self image fileName
            withFileFilters: FileSelectionBrowser saveImageFileNameFilters)

    "Modified: / 30.9.1998 / 23:05:19 / cg"
!

saveImageFileAs: aFileName
    "save the image in aFileName"

    aFileName isNil ifTrue: [^nil].
    image notNil ifTrue:[
        image fileName: aFileName.
        self saveImageOrMask: #image
    ] ifFalse:[
        self warn: 'No image or file name for saving detected!!'
    ]

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

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

    self saveImageMaskFileAs:
        (FileSelectionBrowser
            request: 'Save Image Mask To File'
            fileName: self image fileName 
            withFileFilters: FileSelectionBrowser saveImageFileNameFilters)

    "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:[
        image mask fileName:aFileName.
        self saveImageOrMask: #mask
    ] 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)"

    Object errorSignal handle:[:ex|
        self warn: ex errorString.
    ] 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:[
                |fileName suff|

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

                what = #image ifTrue:[   
                    (fileName := image fileName) isNil ifTrue: [^self error: 'No file name for image detected!!'].
                ].
                what = #mask ifTrue:[   
                    image mask isNil ifTrue: [^self error: 'No image mask to save!!'].
                    (fileName := image mask fileName) isNil ifTrue: [^self error: 'No file name for image mask detected!!'].
                ].
                fileName := fileName asFilename.

                fileName name size = 0 ifTrue: [^self error: 'No file name detected!!'].
                suff := fileName suffix asLowercase.
                (suff = 'tiff') | (suff = 'tif') ifTrue: [imageReaderClass := TIFFReader].
                suff = 'xpm' ifTrue: [imageReaderClass := XPMReader].
                suff = 'xbm' ifTrue: [imageReaderClass := XBMReader].
                suff = 'gif' ifTrue: [imageReaderClass := GIFReader].
                (suff = 'jpg') | (suff = 'jpeg') ifTrue: [imageReaderClass := JPEGReader].
                imageReaderClass isNil ifTrue: [imageReaderClass := XPMReader. image fileName: image fileName, '.xpm'].
                what = #image ifTrue: [image saveOn: image fileName using: imageReaderClass. modified := false].
                what = #mask ifTrue: [image mask saveOn: image mask fileName using: imageReaderClass].
            ]   
        ]
    ]

    "Modified: / 30.9.1998 / 23:19:39 / cg"
!

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) isClass not 
		ifTrue: [^self saveMethodAs].

	    self image storeOn: (imageStoreStream := WriteStream on: '').
	    sel := self resourceSelector.

	    "/ if that method already exists, do not overwrite the category
	    category := 'image specs'.
	    (mthd := cls class compiledMethodAt:sel) notNil ifTrue:[
		category := mthd category.
	    ].

	    imageKey :=  (cls name, ' ', sel) asSymbol.
	    Icon constantNamed: imageKey put:nil.
	    ByteCodeCompiler 
		compile: ((sel,
		    '\', (ResourceSpecEditor codeGenerationCommentForClass: ImageEditor),
		    '\\' , 
		    '    "\',
		    '     self ' , self resourceSelector , ' inspect\',
		    '     ImageEditor openOnClass:self andSelector:#', self resourceSelector, 
		    '\    "',
		    '\\',
		    '    <resource: #image>',
		    '\\',
		    '    ^Icon\') withCRs, 
		    '        constantNamed:#''', imageKey, '''\' withCRs,
		    '        ifAbsentPut:[', imageStoreStream contents, ']')
		forClass: cls class inCategory: category.
	    modified := false.
	]
    ]

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

saveMethodAs

    (self resourceMessage:
	(ResourceSelectionBrowser
	    request: 'Save Image In Class'
	    onSuperclass: #Object
	    andClass: self resourceClass
	    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'!

destroy

    ClipboardMagnification := Clipboard := nil.
    LastMagnification      := magnification.

    super destroy

!

releasePasteDrawing

    (lastPastePoint notNil and: [ClipboardMagnification notNil]) 
    ifTrue: 
    [ 
	self redraw: (lastPastePoint extent: (ClipboardMagnification extent)). 
    ].
    lastPastePoint := ClipboardMagnification := nil
!

releaseUndos

    undoImages removeAll.
    "/ cg: what a kludge - please change to use a valueHolder,
    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/Attic/ImgEditV.st,v 1.109 1999-01-20 19:26:17 cg Exp $'
! !