many many fixes/enhancements
authortz
Wed, 03 Dec 1997 14:34:40 +0100
changeset 627 e0bf28f61361
parent 626 ccc858f815e4
child 628 7f36d8a7735f
many many fixes/enhancements
ImageEditView.st
ImgEditV.st
--- a/ImageEditView.st	Wed Nov 26 22:28:34 1997 +0100
+++ b/ImageEditView.st	Wed Dec 03 14:34:40 1997 +0100
@@ -11,10 +11,10 @@
 "
 
 ImageView subclass:#ImageEditView
-	instanceVariableNames:'magnification gridMagnification antiAlias pixelSelectColor
-		modified imageReaderClass makeRedraw resourceClass
-		resourceSelector'
-	classVariableNames:''
+	instanceVariableNames:'magnification gridMagnification selectColors imageReaderClass
+		resourceClass resourceSelector editMode mouseKeyColorMode
+		undoImage modified coordInfoBlock'
+	classVariableNames:'Clipboard'
 	poolDictionaries:''
 	category:'Views-Misc'
 !
@@ -52,232 +52,6 @@
 "
 ! !
 
-!ImageEditView class methodsFor:'interface specs'!
-
-menuEffects
-    "this window spec was automatically generated by the ST/X MenuEditor"
-
-    "do not manually edit this - the builder may not be able to
-     handle the specification if its corrupted."
-
-    "
-     MenuEditor new openOnClass:ImageEditView andSelector:#menuEffects
-     (Menu new fromLiteralArrayEncoding:(ImageEditView menuEffects)) startUp
-    "
-
-    <resource: #menu>
-
-    ^
-     
-       #(#Menu
-          
-           #(
-             #(#MenuItem
-                #'label:' 'flip - vertical'
-                #'value:' #flipVertical
-            )
-             #(#MenuItem
-                #'label:' 'flip - horizontal'
-                #'value:' #flipHorizontal
-            )
-             #(#MenuItem
-                #'label:' '-'
-            )
-             #(#MenuItem
-                #'label:' 'rotate - clockwise'
-                #'value:' #rotateCW
-            )
-             #(#MenuItem
-                #'label:' 'rotate - counter clockwise'
-                #'value:' #rotateCCW
-            )
-             #(#MenuItem
-                #'label:' '-'
-            )
-             #(#MenuItem
-                #'label:' 'negative'
-                #'value:' #negative
-            )
-             #(#MenuItem
-                #'label:' '-'
-            )
-             #(#MenuItem
-                #'label:' 'resize'
-                #'value:' #resizeImage
-            )
-          ) nil
-          nil
-      )
-! !
-
-!ImageEditView class methodsFor:'menu specs'!
-
-menu
-    "this window spec was automatically generated by the ST/X MenuEditor"
-
-    "do not manually edit this - the builder may not be able to
-     handle the specification if its corrupted."
-
-    "
-     MenuEditor new openOnClass:ImageEditor andSelector:#menu
-     (Menu new fromLiteralArrayEncoding:(ImageEditor menu)) startUp
-    "
-
-    <resource: #menu>
-
-    ^
-
-       #(#Menu
-
-           #(
-             #(#MenuItem
-                #'label:' 'about'
-                #'labelImage:' #(#ResourceRetriever #Launcher #smallAboutIcon)
-                #'submenuChannel:' #menuAbout
-            )
-             #(#MenuItem
-                #'label:' 'file'
-                #'submenu:' 
-                 #(#Menu
-
-                     #(
-                       #(#MenuItem
-                          #'label:' 'new...'
-                          #'value:' #newImage
-                      )
-                       #(#MenuItem
-                          #'label:' '-'
-                      )
-                       #(#MenuItem
-                          #'label:' 'load from file...'
-                          #'value:' #loadFromFile
-                      )
-                       #(#MenuItem
-                          #'label:' 'load from class..'
-                          #'value:' #loadFromClass
-                      )
-                       #(#MenuItem
-                          #'label:' '-'
-                      )
-                       #(#MenuItem
-                          #'label:' 'save'
-                          #'value:' #saveFile
-                          #'enabled:' #canBeSaved
-                      )
-                       #(#MenuItem
-                          #'label:' 'save as...'
-                          #'value:' #saveFileAs
-                          #'enabled:' #isImageLoaded
-                      )
-                       #(#MenuItem
-                          #'label:' '-'
-                      )
-                       #(#MenuItem
-                          #'label:' 'generate image '
-                          #'value:' #generateImage
-                      )
-                       #(#MenuItem
-                          #'label:' 'generate file access'
-                          #'value:' #generateFileAccess
-                      )
-                       #(#MenuItem
-                          #'label:' '-'
-                      )
-                       #(#MenuItem
-                          #'label:' 'exit'
-                          #'value:' #close
-                      )
-                    ) nil
-                    nil
-                )
-            )
-             #(#MenuItem
-                #'label:' 'effects'
-                #'enabled:' #isImageLoaded
-                #'submenu:' 
-                 #(#Menu
-
-                     #(
-                       #(#MenuItem
-                          #'label:' 'flip - vertical'
-                      )
-                       #(#MenuItem
-                          #'label:' 'flip - horizontal'
-                      )
-                       #(#MenuItem
-                          #'label:' '-'
-                      )
-                       #(#MenuItem
-                          #'label:' 'rotate - clockwise'
-                      )
-                       #(#MenuItem
-                          #'label:' 'rotate - counter clockwise'
-                      )
-                       #(#MenuItem
-                          #'label:' '-'
-                      )
-                       #(#MenuItem
-                          #'label:' 'negative'
-                      )
-                       #(#MenuItem
-                          #'label:' '-'
-                      )
-                       #(#MenuItem
-                          #'label:' 'resize'
-                      )
-                    ) nil
-                    nil
-                )
-            )
-             #(#MenuItem
-                #'label:' 'convert'
-                #'enabled:' #isImageLoaded
-                #'submenu:' 
-                 #(#Menu
-
-                     #(
-                       #(#MenuItem
-                          #'label:' '8-plane'
-                          #'argument:' 'color 8-plane'
-                          #'indication:' #'mode:value:'
-                      )
-                       #(#MenuItem
-                          #'label:' '4-plane'
-                          #'argument:' 'color 4-plane'
-                          #'indication:' #'mode:value:'
-                      )
-                       #(#MenuItem
-                          #'label:' '2-plane'
-                          #'argument:' 'color 2-plane'
-                          #'indication:' #'mode:value:'
-                      )
-                       #(#MenuItem
-                          #'label:' '-'
-                      )
-                       #(#MenuItem
-                          #'label:' 'mono'
-                          #'argument:' 'mono'
-                          #'indication:' #'mode:value:'
-                      )
-                    ) nil
-                    nil
-                )
-            )
-             #(#MenuItem
-                #'label:' 'history'
-                #'enabled:' #hasHistory
-                #'submenuChannel:' #menuHistory
-            )
-             #(#MenuItem
-                #'label:' 'help'
-                #'submenuChannel:' #menuHelp
-            )
-          ) nil
-          nil
-      )
-
-! !
-
 !ImageEditView class methodsFor:'startup'!
 
 openOn:aFileName
@@ -303,46 +77,14 @@
 
 !ImageEditView methodsFor:'accessing'!
 
-checkModified
+coordInfoBlock: aBlock
 
-    modified
-    ifTrue:
-    [
-        |aBox|
-        aBox := YesNoBox title:'Image was modified'.        
-        aBox noText:'abort'.
-        aBox yesText:'ignore'.
-        aBox showAtPointer.
-        aBox accepted ifFalse: [^false].
-        modified := false
-    ].
-    ^true
+    coordInfoBlock := aBlock
 !
 
-gridMagnification
-
-    ^gridMagnification
-
-!
-
-gridMagnification:aPathName
-
-    gridMagnification := aPathName
-!
+gridMagnification: aPoint
 
-image:anImage
-
-    |oldMag|
-    (anImage isImage and: [image isNil or: [self checkModified]])
-    ifTrue:
-    [
-        oldMag := magnification.
-        magnification := 1@1.
-        super image: anImage.
-        self magnification:oldMag.
-        ^image
-    ].
-    ^nil
+    gridMagnification := aPoint
 !
 
 imageReaderClass
@@ -356,24 +98,537 @@
 
 !
 
-magnification:aMagnificationPoint
+magnification:aPoint
 
-    magnification ~= aMagnificationPoint
+    magnification ~= aPoint
     ifTrue:
     [
-        magnification := aMagnificationPoint asPoint.
+        magnification := aPoint asPoint.
         self scrollToTopLeft.
         self contentsChanged.
         self invalidate.
     ].
 !
 
-makeRedraw:aBooelean
+resourceClass
+
+    ^resourceClass
+!
+
+resourceClass: aClassOrSymbol
+
+    resourceClass := aClassOrSymbol isClass ifTrue: [aClassOrSymbol name] ifFalse: [aClassOrSymbol asSymbol].
+
+!
+
+resourceMessage
+
+    ^resourceClass, ' ', resourceSelector
+!
+
+resourceMessage: aMessage
+
+    (aMessage notNil and: [aMessage trimBlanks size > 0])
+    ifTrue:
+    [
+        resourceClass := aMessage readStream nextWord asSymbol.
+        resourceSelector := aMessage reversed readStream nextWord reverse asSymbol.
+    ]
+    ifFalse:
+    [
+        ^nil
+    ].
+
+    ^self resourceClass: resourceClass selector: resourceSelector
+
+   
+!
+
+resourceSelector
+
+    ^resourceSelector
+!
+
+resourceSelector: aStringOrSymbol
+
+    resourceSelector := aStringOrSymbol asSymbol
+!
+
+selectedColor
+
+   ^selectColors at: mouseKeyColorMode
+!
+
+selectedColor: aColor
+
+    selectColors at: mouseKeyColorMode put: aColor
+! !
+
+!ImageEditView methodsFor:'accessing menu'!
+
+menuEdit
+    "this window spec was automatically generated by the UI Builder"
+
+    ^ self class menuEdit
+
+
+! !
+
+!ImageEditView methodsFor:'drawing'!
+
+redrawImageX:x y:y width:w height:h
+    |ih iw dotW dotH minX maxX minY maxY color last lastY runW x0 xI yI maskColor|
+
+    ih := image height.
+    iw := image width.
+    dotW := magnification x.
+    dotH := magnification y.
+
+    minX := (x // dotW).
+    minX >= iw ifTrue:[minX := iw - 1].
+    minY := (y // dotH).
+    minY >= ih ifTrue:[minY := ih - 1].
+    maxX := (x + w) // dotW + 1.
+    maxX > iw ifTrue:[maxX := iw].
+    maxY := (y + h) // dotH + 1.
+    maxY > ih ifTrue:[maxY := ih].
+
+    lastY := -1.
+
+    x0 := minX.
+    runW := 0.
+    maskColor := false.
+    image colorsFromX:minX y:minY toX:maxX-1 y:maxY-1 do:
+    [:xx :yy :color|
+
+        yy ~~ lastY ifTrue:
+        [
+            runW ~~ 0 ifTrue:
+            [
+                |origin|
+                origin := (x0 * dotW + margin)@(lastY * dotH + margin).
+                self fillRectangle: (origin extent: (runW@dotH)).                    
+                0 to: runW by: dotW do: [:xxx| self drawFrameAt: ((origin x + xxx) @origin y)].
+                maskColor ifTrue:
+                [
+                    self drawMaskPointAt: origin
+                ].
+                runW := 0.
+            ]. 
+            x0 := xx.
+            lastY := yy.
+        ]. 
 
-    makeRedraw := aBooelean
+        color ~~ last ifTrue:
+        [
+            runW ~~ 0 ifTrue:
+            [
+                |origin|
+                origin := (x0 * dotW + margin)@(yy * dotH + margin).
+                self fillRectangle: (origin extent: (runW@dotH)).
+                0 to: runW by: dotW do: [:xxx| self drawFrameAt: ((origin x + xxx) @origin y)].
+                maskColor ifTrue:
+                [
+                    self drawMaskPointAt: origin
+                ].
+                runW := 0.
+            ].
+
+            self paint: (last := color).
+            image mask notNil ifTrue:
+            [  
+                maskColor := false.
+                (image mask colorAt: xx@yy) = Color black ifTrue:
+                [
+                    self paint: (last := self viewBackground).
+                    maskColor := true.
+                ].
+                last := nil.
+            ].
+            runW := 0.
+            x0 := xx.
+        ].  
+        runW := runW + dotW
+    ].
+    runW ~~ 0 ifTrue:
+    [
+        |origin|
+        origin := (x0 * dotW + margin)@(lastY * dotH + margin).
+        self fillRectangle: (origin extent: runW@dotH).
+        0 to: runW by: dotW do: [:xxx| self drawFrameAt: ((origin x + xxx) @origin y)].
+        maskColor ifTrue:
+        [
+            self drawMaskPointAt: origin.
+        ].
+        runW := 0.
+    ].
+!
+
+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 drawFrame.
+        ^ self
+    ].
+    self clippingRectangle: (x@y extent: w@h). 
+
+    self redrawImageX:x y:y width:w height:h.
+
+    "/ right of image ?
+    adjust == #center ifTrue:
+    [
+        xI := (width - (margin * 2) - ih) // 2.
+        yI := (height - (margin * 2) - iw) // 2.
+    ]
+    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.
+! !
+
+!ImageEditView methodsFor:'edit modes'!
+
+editMode
+
+    editMode isNil ifTrue: [editMode := 'point'].
+    ^editMode
+!
+
+editMode:aMode
+
+    editMode := aMode
+!
+
+mouseKeyColorMode
+
+    ^mouseKeyColorMode printString
+!
+
+mouseKeyColorMode:aMode
+
+    mouseKeyColorMode := aMode asInteger
+! !
+
+!ImageEditView methodsFor:'event handling'!
+
+buttonMotion:state x:x y:y
+
+    self selectedColor notNil & image notNil & (self imageContainsPoint: x@y) & (editMode = 'point')
+        ifTrue: [^self pointAt: x@y].
+
+    ^super buttonMotion:state x:x y:y
+
 !
 
-openFile: aFileName
+buttonPress:button x:x y:y
+
+    self selectedColor notNil & image notNil & (self imageContainsPoint: x@y)
+    ifTrue:
+    [   
+        undoImage := image copy.
+        mouseKeyColorMode := button.
+        (editMode = 'point')   ifTrue: [self pointAt: x@y].
+        (editMode = 'replace') ifTrue: [self replaceAt: x@y].
+        (editMode = 'paste')   ifTrue: [self pasteAt: x@y].
+        (editMode = 'box') | (editMode = 'copy') ifTrue: [self boxAt: x@y].
+        ^self
+    ].
+    
+    ^super buttonPress:button x:x y:y
+! !
+
+!ImageEditView methodsFor:'image drawing'!
+
+boxAt: aPoint
+
+    |firstPoint currentPoint lastCurrentPoint currentExtent imageFirstPoint imageExtent|
+
+    firstPoint := lastCurrentPoint := aPoint//magnification*magnification.
+    [Display anyButtonPressed]
+    whileTrue:
+    [   
+        currentPoint := (0@0) max: (image extent * magnification min: (self translation negated + (device translatePoint: self sensor mousePoint from:device rootView id to:self id))).
+        currentPoint := currentPoint//magnification*magnification.
+        currentExtent := (firstPoint - currentPoint) abs.
+        currentPoint ~= lastCurrentPoint ifTrue:
+        [
+            self redraw: ((firstPoint min: lastCurrentPoint) - 1 extent: (firstPoint - lastCurrentPoint) abs + 2).
+            editMode = 'copy'
+            ifTrue:
+            [
+                self xoring: [self fillRectangle: ((firstPoint min: currentPoint) + 1 extent: currentExtent - 1)]
+            ].
+            editMode = 'box'
+            ifTrue:
+            [
+                self selectedColor ~= Color noColor
+                    ifTrue: [self paint: self selectedColor]
+                    ifFalse: [self paint: self viewBackground].
+                self fillRectangle: ((firstPoint min: currentPoint) + 1 extent: currentExtent - 1)
+            ]. 
+        ]. 
+        self drawLabel: currentPoint//magnification.
+        lastCurrentPoint := currentPoint.
+    ].
+
+    imageFirstPoint := (firstPoint min: currentPoint)//magnification.
+    imageExtent := currentExtent//magnification.
+    editMode = 'box'
+    ifTrue:
+    [
+        self selectedColor ~= Color noColor
+        ifTrue:
+        [   
+            image mask notNil ifTrue: [image mask fillRectangleX: imageFirstPoint x y: imageFirstPoint y width: imageExtent x height: imageExtent y with:Color white].
+            image fillRectangleX: imageFirstPoint x y: imageFirstPoint y width: imageExtent x height: imageExtent y with: self selectedColor.
+            self paint: self selectedColor.
+        ] 
+        ifFalse:
+        [
+            image fillRectangleX: imageFirstPoint x y: imageFirstPoint y width: imageExtent x height: imageExtent y with: ((image colorMap includes: Color black) ifTrue: [Color black] ifFalse: [image colorMap first]).
+            image mask notNil ifTrue: [image mask fillRectangleX: imageFirstPoint x y: imageFirstPoint y width: imageExtent x height: imageExtent y with: Color black].
+            self paint: self viewBackground.
+        ].
+        image restored.
+        modified := true.
+    ].
+    editMode = 'copy'
+    ifTrue:
+    [      
+        Clipboard := image subImageIn: (imageFirstPoint extent: imageExtent - 1)
+    ].
+    self redraw: ((firstPoint min: currentPoint) - 1 extent: (firstPoint - currentPoint) abs + 2).    
+!
+
+pasteAt: aPoint
+
+    Object errorSignal handle:
+    [:ex|
+        WarningBox warn: 'Pasting into this image failed!!'.
+    ] 
+    do:
+    [   
+        |imagePoint|
+        imagePoint := aPoint//magnification.
+        image copyFrom: Clipboard x:0 y:0 toX: imagePoint x y: imagePoint y width: Clipboard width height: Clipboard height.
+        self redraw: (imagePoint * magnification extent: (Clipboard extent * magnification)).
+        self drawLabel: imagePoint.
+        image restored.
+        modified := true.
+    ]
+!
+
+pointAt: aPoint
+
+    |imagePoint|
+    imagePoint := aPoint//magnification.
+    self selectedColor ~= Color noColor
+    ifTrue:
+    [   
+        image mask notNil ifTrue: [image mask colorAt: imagePoint put: Color white].
+        image colorAt: imagePoint put: self selectedColor.
+        self paint: self selectedColor.
+    ] 
+    ifFalse:
+    [
+        image colorAt: imagePoint put: ((image colorMap includes: Color black) ifTrue: [Color black] ifFalse: [image colorMap first]).
+        image mask notNil ifTrue: [image mask colorAt: imagePoint put: Color black].
+        self paint:self viewBackground.
+    ].
+
+    self fillRectangle: (imagePoint * magnification + 1 extent: magnification).
+    self selectedColor = Color noColor
+    ifTrue:
+    [       
+        self drawMaskPointAt: imagePoint * magnification + 1.
+    ].
+    self drawFrameAt: aPoint.
+    self drawLabel: imagePoint.
+    image restored.
+    modified := true.
+!
+
+replaceAt: aPoint
+
+    |imagePoint|
+    imagePoint := aPoint//magnification.
+    self selectedColor ~= Color noColor
+    ifTrue:
+    [   
+        image mask notNil ifTrue: [image mask fillAround: imagePoint withColor: Color white].
+        image fillAround: imagePoint withColor: self selectedColor.
+        self paint: self selectedColor.
+    ] 
+    ifFalse:
+    [
+        image mask notNil ifTrue: [image mask fillAround: imagePoint withColor: Color black].
+        self paint:self viewBackground.
+    ].
+    self drawLabel: imagePoint.
+    self invalidate.
+    image restored.
+    modified := true.
+
+!
+
+undo
+
+    undoImage notNil
+    ifTrue:
+    [
+        modified := false.
+        self image: undoImage.
+        self invalidate
+    ]
+! !
+
+!ImageEditView methodsFor:'image editing'!
+
+flipHorizontal
+
+    self image: image flipHorizontal.
+
+!
+
+flipVertical
+
+    self image: image flipVertical.
+
+!
+
+negativeImage
+
+    self image: image negative.
+
+!
+
+resizeImage
+
+    |b newSize|
+
+    b := EnterBox new.
+    b title:'resize image'.
+    b okText:'apply'.
+    b abortText:'abort'.
+    b initialText:image extent printString.
+    b showAtPointer.
+    (newSize := Object readFromString: b contents onError:nil) notNil
+    ifTrue:
+    [
+        self image: (image magnifiedBy: newSize/image extent)
+    ].
+!
+
+rotateImage
+
+    |b rotation|
+
+    b := EnterBox new.
+    b title:'rotate image'.
+    b okText:'apply'.
+    b abortText:'abort'.
+    b initialText: '0'.
+    b showAtPointer.
+    (rotation := Object readFromString: b contents onError:nil) notNil
+    ifTrue:
+    [   Object errorSignal handle:
+        [:ex|
+            WarningBox warn: 'Image rotation failed.\' withCRs, 'An increase of image depth could help.'.
+        ] 
+        do:
+        [   
+            self image: (image hardRotated: rotation)
+        ]
+    ].
+! !
+
+!ImageEditView methodsFor:'image emphasis'!
+
+drawFrame
+
+    self paint:Color black.
+    "self lineWidth: (magnification x//3 min: 3). "
+    self displayRectangle: ((0@0) extent:(image extent * magnification) + 2).
+    self lineWidth:1.
+!
+
+drawFrameAt: aPoint
+
+    magnification > gridMagnification
+    ifTrue:
+    [   
+        |lineStartingPoint lineEndingPoint oldColor|
+        lineStartingPoint := aPoint//magnification*magnification.
+        lineEndingPoint   := aPoint//magnification*magnification + magnification.
+        oldColor := self paint.
+        self xoring:
+        [
+            self displayLineFrom: lineEndingPoint 
+                              to: (lineEndingPoint x)@(lineStartingPoint y).
+            self displayLineFrom: lineEndingPoint 
+                              to: (lineStartingPoint x)@(lineEndingPoint y).
+        ].
+        self paint: oldColor.
+    ]
+!
+
+drawLabel: aLabel
+    coordInfoBlock notNil
+    ifTrue:
+    [         
+        coordInfoBlock value: aLabel printString
+    ]
+!
+
+drawMaskPointAt: aPoint
+
+    |sizeOfMaskPoint|
+    sizeOfMaskPoint := magnification//3.
+    self xoring: [self fillRectangle: (aPoint + sizeOfMaskPoint extent: sizeOfMaskPoint)].
+   
+! !
+
+!ImageEditView methodsFor:'image setting'!
+
+image:anImage
+
+    (anImage isImage and: [image isNil or: [self checkModified]])
+    ifTrue:
+    [
+        super image: anImage.
+        image photometric = #palette
+        ifTrue:
+        [
+            (image usedColors includes: selectColors first) ifFalse: [selectColors at: 1 put: nil].
+            (image usedColors includes: selectColors last) ifFalse: [selectColors at: 2 put: nil].
+        ].
+        ^self
+    ].
+    ^nil
+!
+
+loadFromFile: aFileName
 
     |fileName newImage|
     fileName := aFileName asFilename.
@@ -396,409 +651,19 @@
     ]
 !
 
-pixelSelectColor: aColor
-
-    pixelSelectColor := aColor
-!
-
-resourceClass
-
-    ^resourceClass
-!
-
-resourceClass: aClass
-
-    resourceClass := aClass
-!
+resourceClass: aClassOrSymbol selector: aStringOrSymbol
 
-resourceClass: aClass selector: aSelector
-
-    resourceClass := aClass.
-    resourceSelector := aSelector.
-    (aClass isClass and: [aClass class implements: aSelector])
-    ifTrue:
-    [   
-        ^self image: (aClass perform: aSelector)
-    ].
-    ^nil
-!
-
-resourceMessage
-
-    (resourceClass value notNil and: [resourceSelector value notNil])
+    |aClass|
+    imageReaderClass := nil.
+    self resourceClass: aClassOrSymbol.
+    self resourceSelector: aStringOrSymbol.
+    aClass := Smalltalk at: resourceClass. 
+    (aClass isClass and: [aClass class implements: resourceSelector])
     ifTrue:
     [ 
-        ^resourceClass name, ' ', resourceSelector
+        ^self image: (aClass perform: resourceSelector) copy
     ].
     ^nil
-!
-
-resourceMessage: aMessage
-
-    aMessage isNil ifTrue: [^nil].
-    resourceClass := Smalltalk at: aMessage copy readStream nextWord asSymbol.
-    resourceSelector := aMessage copy reverse readStream nextWord reverse asSymbol.
-
-    ^self resourceClass: resourceClass selector: resourceSelector
-
-   
-!
-
-resourceSelector
-
-    ^resourceSelector
-!
-
-resourceSelector: aSelector
-
-    resourceSelector := aSelector
-! !
-
-!ImageEditView methodsFor:'accessing menu'!
-
-menuEffects
-    "this window spec was automatically generated by the UI Builder"
-
-    ^ self class menuEffects
-
-
-! !
-
-!ImageEditView methodsFor:'drawing'!
-
-colorAt: aPoint put: aColor
-
-    |tempPaint|
-    tempPaint := self paint.
-    aColor redByte = 'mask'
-    ifTrue:
-    [       
-        image restored; colorAt: aPoint//magnification put: Color black.
-        image mask notNil ifTrue: [image mask restored; colorAt: aPoint//magnification put: Color black].
-        self paint:Color lightGray.
-    ]
-    ifFalse:
-    [
-        image mask notNil ifTrue: [image mask restored; colorAt: aPoint//magnification put: Color white].
-        image restored; colorAt: aPoint//magnification put: aColor.
-        self paint:aColor.
-    ].
-
-    self fillRectangleX:(aPoint x // magnification x) * magnification x + 1
-        y:(aPoint y // magnification y) * magnification y + 1
-        width:magnification x  height:magnification y.
-
-    self paint:tempPaint.
-    magnification > gridMagnification
-    ifTrue:
-    [
-        self drawGridMagnification
-    ].
-
-!
-
-drawGridMagnification
-
-    |tempPaint|
-    tempPaint := self paint.
-    self paint:Color black.
-    0 to: (image width * magnification x) by: magnification x do:
-    [:x|
-        self displayLineFromX:x y:0 toX:x y:(image height * magnification y)
-    ].
-    0 to: (image height * magnification y) by: magnification y do:
-    [:y|
-        self displayLineFromX:0 y:y toX:(image width * magnification x) y:y
-    ].
-    self paint:tempPaint.
-!
-
-redrawImageX:x y:y width:w height:h
-    |ih iw dotW dotH minX maxX minY maxY color last lastY runW x0 xI yI|
-
-    ih := image height.
-    iw := image width.
-    dotW := magnification x.
-    dotH := magnification y.
-
-    minX := (x // dotW).
-    minX > iw ifTrue:[
-        minX := iw - 1
-    ].
-
-    minY := (y // dotH) .
-    minY > ih ifTrue:[
-        minY := ih - 1
-    ].
-    maxX := (x + w) // dotW + 1.
-    maxX > iw ifTrue:[
-        maxX := iw
-    ].
-    maxY := (y + h) // dotH + 1.
-    maxY > ih ifTrue:[ 
-        maxY := ih
-    ].
-
-    lastY := -1.
-
-    x0 := minX.
-    runW := 0.
-
-    image colorsFromX:minX y:minY toX:maxX-1 y:maxY-1 do:[:xx :yy :color |
-
-        yy ~~ lastY ifTrue:[
-            runW ~~ 0 ifTrue:[
-                self fillRectangleX:(x0 * dotW + margin)
-                                  y:(lastY * dotH + margin)
-                              width:runW height:dotH.
-                runW := 0.
-            ]. 
-            x0 := xx.
-            lastY := yy.
-        ]. 
-
-        color ~~ last ifTrue:[
-            runW ~~ 0 ifTrue:[
-                self fillRectangleX:(x0 * dotW + margin)
-                                  y:(yy * dotH + margin)
-                              width:runW height:dotH.
-                runW := 0.
-            ].
-
-            "self paint:color."
-            (image mask notNil and: [(image mask colorAt: xx@yy) = Color black])
-                ifTrue: [self paint: Color lightGray] ifFalse: [self paint: color].
-            last := color.
-            runW := 0.
-            x0 := xx.
-        ].  
-        runW := runW + dotW
-    ].
-    runW ~~ 0 ifTrue:[
-        self fillRectangleX:(x0 * dotW + margin)
-                          y:(lastY * dotH + margin)
-                      width:runW height:dotH.
-        runW := 0.
-    ].
-!
-
-redrawX:x y:y width:w height:h
-    |ih iw dotW dotH minX maxX minY maxY color last lastY runW x0 xI yI|
-
-    image isNil ifTrue:[^self].
-
-    magnification = (1@1) ifTrue:[
-        super redrawX:x y:y width:w height:h.
-        ^ self
-    ].
-    self clippingRectangle: (x@y extent: w@h). 
-
-    self redrawImageX:x y:y width:w height:h.
-
-    "/ right of image ?
-    adjust == #center ifTrue:[
-            xI := (width - (margin * 2) - ih) // 2.
-            yI := (height - (margin * 2) - iw) // 2.
-        ] 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)  
-    ].
-    magnification > gridMagnification
-    ifTrue:
-    [
-        self drawGridMagnification
-    ].
-    self clippingRectangle: nil
-! !
-
-!ImageEditView methodsFor:'event handling'!
-
-buttonMotion:state x:x y:y
-
-    self showColorAtX:x y:y.
-!
-
-buttonMultiPress:button x:x y:y
-    button == 1 ifTrue:[
-        |clr|
-        clr := self getColorAtX:x y:y.
-    ].
-    super buttonMultiPress:button x:x y:y
-
-    "Created: 8.5.1996 / 00:18:06 / stefan"
-!
-
-buttonPress:button x:x y:y
-    button == 1 ifTrue:[
-        self showColorAtX:x y:y.
-        ^ self
-    ].
-    super buttonPress:button x:x y:y
-!
-
-getColorAtX:x y:y
-    |pi|
-
-    pi := (((x @ y) - margin + 1) / magnification)  floor.
-    ((0@0 corner:(image extent) - 1) containsPoint:pi)
-    ifTrue:
-    [
-        ^ image at:pi
-    ].
-    ^ nil
-
-    "Created: 8.5.1996 / 00:15:55 / stefan"
-!
-
-showColorAtX:x y:y
-    |clr|
-
-    clr := self getColorAtX:x y:y.
-    clr notNil
-    ifTrue:
-    [
-        pixelSelectColor isColor" & (image colorMap includes: clr)"
-        ifTrue:
-        [   
-            makeRedraw ifTrue: [self invalidate. makeRedraw := false].
-            modified := true.
-            self colorAt: x@y put: pixelSelectColor.
-        ]
-    ]
-! !
-
-!ImageEditView methodsFor:'image conversion'!
-
-convertToColor24
-    (Depth24Image fromImage:image) inspect
-
-    "Modified: 3.6.1997 / 18:34:34 / cg"
-!
-
-convertToColor4
-    (Depth4Image fromImage:image) inspect
-
-    "Modified: 3.6.1997 / 18:34:45 / cg"
-!
-
-convertToColor8
-    (Depth8Image fromImage:image) inspect
-
-    "Created: 3.6.1997 / 18:34:08 / cg"
-    "Modified: 3.6.1997 / 18:34:51 / cg"
-!
-
-convertToGray2
-    (image asFloydSteinbergDitheredGrayImageDepth:2) inspect
-
-    "Created: 3.6.1997 / 18:34:02 / cg"
-    "Modified: 3.6.1997 / 18:39:23 / cg"
-!
-
-convertToGray4
-    (image asFloydSteinbergDitheredGrayImageDepth:4) inspect
-
-    "Created: 3.6.1997 / 18:34:04 / cg"
-    "Modified: 3.6.1997 / 18:39:20 / cg"
-!
-
-convertToGray8
-    (image asFloydSteinbergDitheredGrayImageDepth:8) inspect
-
-    "Created: 3.6.1997 / 18:34:05 / cg"
-    "Modified: 3.6.1997 / 18:39:16 / cg"
-!
-
-convertToMono
-    (image asFloydSteinbergDitheredGrayImageDepth:1) inspect
-
-    "Created: 3.6.1997 / 18:33:42 / cg"
-    "Modified: 3.6.1997 / 18:39:26 / cg"
-! !
-
-!ImageEditView methodsFor:'image processing'!
-
-flipHorizontal
-    self performImageOperation:#flipHorizontal withArguments:nil
-!
-
-flipVertical
-    self performImageOperation:#flipVertical withArguments:nil
-!
-
-negative
-    self performImageOperation:#negative withArguments:nil 
-!
-
-performImageOperation:operation withArguments:args
-    |oldMag newImage|
-
-    windowGroup withCursor:Cursor wait do:[
-        oldMag := magnification.
-        magnification := 1@1.
-        newImage := image perform:operation withArguments:args.
-        newImage isNil ifTrue:[
-            self information:'conversion failed - revert to original'.
-            ^ self
-        ].
-        image := newImage.
-        self clear.
-        (oldMag isNil or:[oldMag = magnification]) ifTrue:[
-            self invalidate
-        ] ifFalse:[
-            self magnification:oldMag.
-        ]
-    ]
-
-    "Modified: 23.6.1997 / 09:49:26 / cg"
-!
-
-resizeImage
-    |b newSize newImage wNew hNew bits|
-
-    b := EnterBox new.
-    b title:'new size (x @ y) contents will be located at top-left'.
-    b okText:'apply'.
-    b abortText:'abort'.
-    b action:[:string | newSize := Object readFromString:string onError:nil].
-    b initialText:(image extent printString).
-    b showAtPointer.
-
-    newSize notNil ifTrue:[
-        wNew := image width min:newSize x.
-        hNew := image height min:newSize y.
-
-        newImage := Image 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)).
-
-        newImage copyFrom:image x:0 y:0 toX:0 y:0 width:wNew height:hNew.
-
-        self image: newImage
-    ].
-
-    "Created: 31.7.1997 / 11:41:14 / cg"
-    "Modified: 31.7.1997 / 13:45:47 / cg"
-!
-
-rotateCCW
-    self performImageOperation:#rotated: withArguments:#(270)
-!
-
-rotateCW
-    self performImageOperation:#rotated: withArguments:#(90)
 ! !
 
 !ImageEditView methodsFor:'initialization'!
@@ -806,197 +671,14 @@
 initialize
 
     super initialize.
+
     magnification := 1@1.
-    gridMagnification := 5@5.
-    makeRedraw := modified := antiAlias := false.
-
-    self menuHolder:self; menuPerformer:self; menuMessage:#imageMenu.
-
-    "Modified: 2.6.1997 / 15:49:00 / cg"
-! !
-
-!ImageEditView methodsFor:'menu'!
-
-imageMenu
-    |m convertMenu labels selectors|
-
-    image mask notNil ifTrue:[
-        labels := #(
-                        'save as ...'
-                        'save mask as ...'
-                       ).
-        selectors := #(
-                        saveAs
-                        saveMaskAs
-                      ).
-        magnification ~~ (1@1) notNil ifTrue:[
-            labels := labels , #(
-                        '-'
-                        'save magnified as ...'
-                        'save magnified mask as ...'
-                       ).
-
-            selectors := selectors , #(
-                        nil
-                        saveMagnifiedAs
-                        saveMagnifiedMaskAs
-                      ).
-        ]
-    ] ifFalse:[
-        labels := #(
-                        'save as ...'
-                       ).
-        selectors := #(
-                        saveAs
-                      ).
-        magnification ~~ (1@1) ifTrue:[
-            labels := labels , #(
-                        '-'
-                        'save magnified as ...'
-                       ).
-
-            selectors := selectors , #(
-                        nil
-                        saveMagnifiedAs
-                      ).
-        ]
-    ].
-
-    labels := labels , #(
-                            '-'
-                            'print'
-                            'print magnified'
-                            '-'
-                            'magnification'
-                            'magnify & antiAlias'
-"/                            'colors'
-                            'effects'
-                            'convert to'
-                        ).
-    selectors := selectors , #(
-                        nil
-                        doPrint
-                        doPrintMagnified
-                        nil
-                        changeMagnification
-                        changeMagnificationAndAntiAlias
-"/                        showColors
-                        effects
-                        convert
-                        ).
-
-    m := PopUpMenu
-               labels:(resources array:labels)
-            selectors:selectors
-             receiver:self
-                  for:self.
-
-    magnification = 1 ifTrue:[
-        m disable:#doPrintMagnified
-    ].
-
-    m subMenuAt:#effects put:(
-        PopUpMenu labels:(resources array:#(
-                            'flip - vertical'
-                            'flip - horizontal'
-                            '-'
-                            'rotate - clockwise'
-                            'rotate - counter clockwise'
-                            '-'
-                            'negative'
-                            '-'
-                            'resize'
-"
-                            'blurr'
-"
-                           ))
-               selectors:#(
-                            flipVertical
-                            flipHorizontal
-                            nil
-                            rotateCW
-                            rotateCCW
-                            nil
-                            negative
-                            nil
-                            resizeImage
-"
-                            blurr
-"
-                           )
-                receiver:self
-                     for:self
-
-    ).
-
-    m subMenuAt:#convert put:(
-        convertMenu :=
-        PopUpMenu labels:(resources array:#(
-                            'monochrome (dither)'
-                            '-'
-                            'gray 2-plane (dither)'
-                            'gray 4-plane (dither) '
-                            'gray 8-plane '
-                            '-'
-"/                            'color 4-plane (dither)'
-"/                            'color 8-plane (dither)'
-                            'color 24-plane'
-                           ))
-               selectors:#(
-                            convertToMono
-                            nil
-                            convertToGray2
-                            convertToGray4
-                            convertToGray8
-                            nil
-"/                            convertToColor4
-"/                            convertToColor8
-                            convertToColor24
-                           )
-                receiver:self
-                     for:self
-    ).
-
-    image depth == 1 ifTrue:[
-        convertMenu disable:#convertToMono
-    ].
-    image depth == 2 ifTrue:[
-        (image photometric ~~ #palette
-        and:[image photometric ~~ #rgb]) ifTrue:[
-            convertMenu disable:#convertToGray2
-        ]
-    ].
-    image depth == 4 ifTrue:[
-        (image photometric ~~ #palette
-        and:[image photometric ~~ #rgb]) ifTrue:[
-            convertMenu disable:#convertToGray4
-        ] ifFalse:[
-            convertMenu disable:#convertToColor4
-        ]
-    ].
-    image depth == 8 ifTrue:[
-        (image photometric ~~ #palette
-        and:[image photometric ~~ #rgb]) ifTrue:[
-            convertMenu disable:#convertToGray8
-        ] ifFalse:[
-            convertMenu disable:#convertToColor8
-        ]
-    ].
-    image depth == 24 ifTrue:[
-        image photometric == #rgb ifTrue:[
-            convertMenu disable:#convertToColor24
-        ]
-    ].
-
-    ^ m
-
-    "
-     ImageEditView openOn:'bitmaps/SBrowser.xbm'
-     ImageEditView openOn:'bitmaps/garfield.gif'
-    "
-
-    "Created: 20.2.1997 / 18:47:17 / cg"
-    "Modified: 31.7.1997 / 11:41:26 / cg"
+    gridMagnification := 8@8.
+    modified := false.
+    mouseKeyColorMode := 1.
+    resourceClass := resourceSelector := ''.
+    selectColors := Array with: nil with: nil.
+    self menuHolder:self; menuPerformer:self; menuMessage:#imageMenu. 
 ! !
 
 !ImageEditView methodsFor:'menu actions'!
@@ -1013,81 +695,35 @@
     b showAtPointer.
 
     newMag notNil ifTrue:[
-        antiAlias ifTrue:[
-            magnification := nil.
-        ].
-        antiAlias := false.
         self magnification:newMag.
     ].
 
     "Modified: 31.7.1997 / 11:43:12 / cg"
 !
 
-changeMagnificationAndAntiAlias
-    |b newMag|
-
-    b := EnterBox new.
-    b title:'magnification (magX @ magY)'.
-    b okText:'apply'.
-    b abortText:'abort'.
-    b action:[:string | newMag := (Object readFromString:string onError:nil)].
-    b initialText:(magnification printString).
-    b showAtPointer.
+loadFromClass
 
-    newMag notNil ifTrue:[
-        antiAlias ifFalse:[
-            magnification := nil.
-        ].
-        antiAlias := true.
-        self magnification:newMag
-    ].
+    self resourceMessage: (ResourceBrowserView
+        openOnSuperclass: ApplicationModel
+        class: self resourceClass
+        selector: self resourceSelector
+        resourceTypes: #(#image #fileImage))
+        
 
-    "Created: 2.6.1997 / 15:51:01 / cg"
-    "Modified: 31.7.1997 / 11:43:47 / cg"
 !
 
-createFileName
+loadFromUser
 
-    image fileName notNil
-    ifFalse:
-    [   
-        |fileName|
-        (fileName := FileBrowserView requestFileName) notNil
-        ifTrue:
-        [    self halt.
-            image fileName: fileName.
-            ^true
-        ].
-    ].
-    ^true.
+    self image: 
+        ((Image fromUser)
+            asDitheredTrueColor8FormOn: Display)
+
 !
 
-createResourceMessage
+print
+    |stream psgc|
 
-    (self resourceClass class implements: self resourceSelector)
-    ifFalse:
-    [   
-        ((ResourceBrowserView
-            openOnSuperclass: #ApplicationModel
-            class: resourceClass
-            selector: resourceSelector
-            resourceTypes: #(#image #fileImage))) notNil
-        ifTrue:
-        [
-            ^true
-        ].
-    ].
-    ^false.
-!
-
-doPrint
-    self doPrint:image
-
-    "Modified: 2.6.1997 / 18:32:11 / cg"
-!
-
-doPrint:anImage
-    |stream psgc|
+    image isNil ifTrue: [^nil].
 
     Printer supportsPostscript ifFalse:[
         self warn:'need a postscript printer'.
@@ -1102,131 +738,32 @@
 
     self withWaitCursorDo:[
         psgc := PSGraphicsContext on:stream. "/  extent:(1.0 @ 1.0).
-        psgc displayForm:anImage x:0 y:0.
+        psgc displayForm: (image magnifiedBy: magnification) x:0 y:0.
         psgc close.
     ]
-
-    "Modified: 28.5.1997 / 10:54:11 / cg"
-    "Created: 2.6.1997 / 18:32:03 / cg"
-!
-
-doPrintMagnified
-    "self doPrint:(magnifiedImage ? image)"
-
-    "Modified: 2.6.1997 / 18:31:54 / cg"
-!
-
-doSaveImageAs:anImage title:aTitle
-    "save contents into a file 
-     - ask user for filename using a fileSelectionBox."
-
-    |fileName imgFileName defaultName rdr i txt suffix|
-
-    defaultName := pathName ? ''.
-
-    pathName isNil ifTrue:[
-        suffix := 'tiff'.
-        (imgFileName := image fileName) notNil ifTrue:[
-            suffix := imgFileName asFilename suffix.
-            defaultName := imgFileName asFilename baseName
-        ]
-    ] ifFalse:[
-        suffix := pathName asFilename suffix.
-        "/ a supported suffix ?
-        ((rdr := Image imageReaderClassForSuffix:suffix) isNil 
-        or:[(rdr canRepresent:anImage) not]) ifTrue:[
-            suffix := 'tiff'.
-            defaultName := (pathName asFilename withSuffix:suffix) pathName
-        ].
-    ].
-
-    Image cannotRepresentImageSignal handle:[:ex |
-        self warn:('cannot represent this image in that format.\\(%1)' bindWith:ex errorString) withCRs.
-        fileName := nil.
-        ex restart
-    ] do:[
-        fileName := Dialog
-                        requestFileName:(resources string:aTitle)
-                        default:defaultName
-                        ok:(resources string:'save')
-                        abort:(resources string:'abort')
-                        pattern:('*.' , suffix).
-
-        fileName notNil ifTrue:[
-            anImage saveOn:fileName.
-        ].
-    ].
-    pathName := fileName.
-
-    "Created: / 20.2.1997 / 18:52:08 / cg"
-    "Modified: / 3.11.1997 / 15:02:27 / cg"
-!
-
-generateFileAccess
-
-    self createFileName
-    ifTrue:
-    [
-        |compileString stream|
-        stream := WriteStream on: ''.
-        self image storeOn: stream.
-        compileString :=
-            self resourceSelector,
-            '\\' withCRs,
-            '    <resource: #fileImage>\' withCRs,
-            '    ^Image fromFile:''',
-            image fileName, ''''.
-        ByteCodeCompiler compile: compileString forClass: self resourceClass class inCategory: 'image specs'.
-    ]
-!
-
-generateImage
-
-    "self createResourceMessage
-    ifTrue:
-    ["
-        |compileString stream|  
-        stream := WriteStream on: ''.
-        self image storeOn: stream.
-        compileString :=
-            self resourceSelector,
-            '\\' withCRs,
-            '    <resource: #image>\' withCRs,
-            '    ^',
-            stream contents.   
-        ByteCodeCompiler compile: compileString forClass: self resourceClass class inCategory: 'image specs'.
-    "]"   
-!
-
-loadFromClass
-
-    self resourceMessage: (ResourceBrowserView
-        openOnSuperclass: ApplicationModel
-        class: self resourceClass
-        selector: self resourceSelector
-        resourceTypes: #(#image #fileImage))
-        
-
 !
 
 save
 
-    |fileName|
-    fileName := image fileName.
     Object errorSignal handle:
-    [:exeption|
-        WarningBox warn: exeption errorString.
-        ^nil
+    [:ex|
+        WarningBox warn: ex errorString.
+        ^nil                                 
     ] 
     do:
-    [
+    [   
+        |fileName|
+        image isNil ifTrue: [^self error: 'No image to save!!'].
+        image fileName isNil ifTrue: [^self error: 'No file name for image detected!!'].
+        fileName := image fileName asFilename.
         (fileName suffix = 'tiff') | (fileName suffix = 'tif') ifTrue: [imageReaderClass := TIFFReader].
         fileName suffix = 'xpm' ifTrue: [imageReaderClass := XPMReader].
         fileName suffix = 'xbm' ifTrue: [imageReaderClass := XBMReader].
         fileName suffix = 'gif' ifTrue: [imageReaderClass := GIFReader].
         (fileName suffix = 'jpg') | (fileName suffix = 'jpeg') ifTrue: [imageReaderClass := JPEGReader].
-        imageReaderClass isNil ifTrue: [^self error: 'no appropriate image reader found'].
-        image saveOn: fileName using: imageReaderClass.
+        imageReaderClass isNil ifTrue: [imageReaderClass := XPMReader. image fileName: image fileName, '.xpm'].
+        
+        image saveOn: image fileName using: imageReaderClass.
         modified := false.
     ]
        
@@ -1236,42 +773,76 @@
     "save contents into a file 
      - ask user for filename using a fileSelectionBox."
 
-    self doSaveImageAs:image title:'save image in:'
-
-    "Modified: 20.2.1997 / 18:52:37 / cg"
-!
-
-saveMagnifiedAs
-    "save contents into a file 
-     - ask user for filename using a fileSelectionBox."
-
-    "self doSaveImageAs:magnifiedImage title:'save magnified image in:' "
-
-    "Created: 20.2.1997 / 18:52:53 / cg"
+    self saveImageFileAs
 !
 
-saveMagnifiedMaskAs
-    "save contents into a file 
-     - ask user for filename using a fileSelectionBox."
+saveAsMethod
 
-    "self doSaveImageAs:(magnifiedImage mask) title:'save magnified mask in:'"
-
-    "Created: 20.2.1997 / 18:53:31 / cg"
-    "Modified: 20.2.1997 / 18:56:48 / cg"
+    Object errorSignal handle:
+    [:ex|
+        WarningBox warn: ex errorString.
+        ^nil                                 
+    ] 
+    do:
+    [   
+        |compileString stream aClass|  
+        stream := WriteStream on: ''.
+        self resourceSelector trimBlanks size = 0 ifTrue: [^self error: 'No image selector detected'].
+        (aClass := Smalltalk at: self resourceClass) isClass ifFalse: [^self error: 'No class for image selector detected'].
+        self image storeOn: stream.
+        compileString :=
+            self resourceSelector,
+            '\\' withCRs,
+            '    <resource: #image>\' withCRs,
+            '    ^',
+            stream contents.   
+        ByteCodeCompiler compile: compileString forClass: aClass class inCategory: 'resources'.
+        modified := false.
+    ]
 !
 
-saveMaskAs
-    "save contents into a file 
-     - ask user for filename using a fileSelectionBox."
+saveImageFileAs
+
+    |aFileName|
+
+    (aFileName := (FileBrowserView requestFileName: self image fileName fileFilters: #('*.xpm' '*.gif'))) notNil
+    ifTrue:
+    [
+        self saveImageFileAs: aFileName
+    ].
+!
 
-    self doSaveImageAs:(image mask) title:'save mask in:'
+saveImageFileAs: aFileName
 
-    "Created: 20.2.1997 / 18:51:06 / cg"
-    "Modified: 20.2.1997 / 18:56:54 / cg"
+    image notNil
+    ifTrue:
+    [
+        image fileName: aFileName.
+        self save
+    ]
+    ifFalse:
+    [
+        WarningBox warn: 'No image detected'
+    ]
 ! !
 
 !ImageEditView methodsFor:'queries'!
 
+checkModified
+
+    modified ifTrue:
+    [
+        |aBox|
+        aBox := YesNoBox title:'Image was modified'.        
+        aBox noText:'abort'.
+        aBox yesText:'ignore'.
+        aBox showAtPointer.
+        aBox accepted ifFalse: [^false].
+        modified := false
+    ].
+    ^true
+!
+
 heightOfContents
     "return the images height"
 
@@ -1279,6 +850,13 @@
     ^ (image height * magnification y) rounded
 !
 
+imageContainsPoint: aPoint
+    |pi|
+    image isNil ifTrue: [^false].
+    pi := ((aPoint - margin + 1) / magnification) floor.
+    ^((0@0 corner:(image extent) - 1) containsPoint:pi)
+!
+
 widthOfContents
     "return the images width"
 
@@ -1286,8 +864,18 @@
     ^ (image width * magnification x) rounded
 ! !
 
+!ImageEditView methodsFor:'release'!
+
+destroy
+
+    undoImage := nil.
+    Clipboard := nil.
+    super destroy.
+
+! !
+
 !ImageEditView class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libwidg2/ImageEditView.st,v 1.48 1997-11-26 18:53:45 tz Exp $'
+    ^ '$Header: /cvs/stx/stx/libwidg2/ImageEditView.st,v 1.49 1997-12-03 13:34:40 tz Exp $'
 ! !
--- a/ImgEditV.st	Wed Nov 26 22:28:34 1997 +0100
+++ b/ImgEditV.st	Wed Dec 03 14:34:40 1997 +0100
@@ -11,10 +11,10 @@
 "
 
 ImageView subclass:#ImageEditView
-	instanceVariableNames:'magnification gridMagnification antiAlias pixelSelectColor
-		modified imageReaderClass makeRedraw resourceClass
-		resourceSelector'
-	classVariableNames:''
+	instanceVariableNames:'magnification gridMagnification selectColors imageReaderClass
+		resourceClass resourceSelector editMode mouseKeyColorMode
+		undoImage modified coordInfoBlock'
+	classVariableNames:'Clipboard'
 	poolDictionaries:''
 	category:'Views-Misc'
 !
@@ -52,232 +52,6 @@
 "
 ! !
 
-!ImageEditView class methodsFor:'interface specs'!
-
-menuEffects
-    "this window spec was automatically generated by the ST/X MenuEditor"
-
-    "do not manually edit this - the builder may not be able to
-     handle the specification if its corrupted."
-
-    "
-     MenuEditor new openOnClass:ImageEditView andSelector:#menuEffects
-     (Menu new fromLiteralArrayEncoding:(ImageEditView menuEffects)) startUp
-    "
-
-    <resource: #menu>
-
-    ^
-     
-       #(#Menu
-          
-           #(
-             #(#MenuItem
-                #'label:' 'flip - vertical'
-                #'value:' #flipVertical
-            )
-             #(#MenuItem
-                #'label:' 'flip - horizontal'
-                #'value:' #flipHorizontal
-            )
-             #(#MenuItem
-                #'label:' '-'
-            )
-             #(#MenuItem
-                #'label:' 'rotate - clockwise'
-                #'value:' #rotateCW
-            )
-             #(#MenuItem
-                #'label:' 'rotate - counter clockwise'
-                #'value:' #rotateCCW
-            )
-             #(#MenuItem
-                #'label:' '-'
-            )
-             #(#MenuItem
-                #'label:' 'negative'
-                #'value:' #negative
-            )
-             #(#MenuItem
-                #'label:' '-'
-            )
-             #(#MenuItem
-                #'label:' 'resize'
-                #'value:' #resizeImage
-            )
-          ) nil
-          nil
-      )
-! !
-
-!ImageEditView class methodsFor:'menu specs'!
-
-menu
-    "this window spec was automatically generated by the ST/X MenuEditor"
-
-    "do not manually edit this - the builder may not be able to
-     handle the specification if its corrupted."
-
-    "
-     MenuEditor new openOnClass:ImageEditor andSelector:#menu
-     (Menu new fromLiteralArrayEncoding:(ImageEditor menu)) startUp
-    "
-
-    <resource: #menu>
-
-    ^
-
-       #(#Menu
-
-           #(
-             #(#MenuItem
-                #'label:' 'about'
-                #'labelImage:' #(#ResourceRetriever #Launcher #smallAboutIcon)
-                #'submenuChannel:' #menuAbout
-            )
-             #(#MenuItem
-                #'label:' 'file'
-                #'submenu:' 
-                 #(#Menu
-
-                     #(
-                       #(#MenuItem
-                          #'label:' 'new...'
-                          #'value:' #newImage
-                      )
-                       #(#MenuItem
-                          #'label:' '-'
-                      )
-                       #(#MenuItem
-                          #'label:' 'load from file...'
-                          #'value:' #loadFromFile
-                      )
-                       #(#MenuItem
-                          #'label:' 'load from class..'
-                          #'value:' #loadFromClass
-                      )
-                       #(#MenuItem
-                          #'label:' '-'
-                      )
-                       #(#MenuItem
-                          #'label:' 'save'
-                          #'value:' #saveFile
-                          #'enabled:' #canBeSaved
-                      )
-                       #(#MenuItem
-                          #'label:' 'save as...'
-                          #'value:' #saveFileAs
-                          #'enabled:' #isImageLoaded
-                      )
-                       #(#MenuItem
-                          #'label:' '-'
-                      )
-                       #(#MenuItem
-                          #'label:' 'generate image '
-                          #'value:' #generateImage
-                      )
-                       #(#MenuItem
-                          #'label:' 'generate file access'
-                          #'value:' #generateFileAccess
-                      )
-                       #(#MenuItem
-                          #'label:' '-'
-                      )
-                       #(#MenuItem
-                          #'label:' 'exit'
-                          #'value:' #close
-                      )
-                    ) nil
-                    nil
-                )
-            )
-             #(#MenuItem
-                #'label:' 'effects'
-                #'enabled:' #isImageLoaded
-                #'submenu:' 
-                 #(#Menu
-
-                     #(
-                       #(#MenuItem
-                          #'label:' 'flip - vertical'
-                      )
-                       #(#MenuItem
-                          #'label:' 'flip - horizontal'
-                      )
-                       #(#MenuItem
-                          #'label:' '-'
-                      )
-                       #(#MenuItem
-                          #'label:' 'rotate - clockwise'
-                      )
-                       #(#MenuItem
-                          #'label:' 'rotate - counter clockwise'
-                      )
-                       #(#MenuItem
-                          #'label:' '-'
-                      )
-                       #(#MenuItem
-                          #'label:' 'negative'
-                      )
-                       #(#MenuItem
-                          #'label:' '-'
-                      )
-                       #(#MenuItem
-                          #'label:' 'resize'
-                      )
-                    ) nil
-                    nil
-                )
-            )
-             #(#MenuItem
-                #'label:' 'convert'
-                #'enabled:' #isImageLoaded
-                #'submenu:' 
-                 #(#Menu
-
-                     #(
-                       #(#MenuItem
-                          #'label:' '8-plane'
-                          #'argument:' 'color 8-plane'
-                          #'indication:' #'mode:value:'
-                      )
-                       #(#MenuItem
-                          #'label:' '4-plane'
-                          #'argument:' 'color 4-plane'
-                          #'indication:' #'mode:value:'
-                      )
-                       #(#MenuItem
-                          #'label:' '2-plane'
-                          #'argument:' 'color 2-plane'
-                          #'indication:' #'mode:value:'
-                      )
-                       #(#MenuItem
-                          #'label:' '-'
-                      )
-                       #(#MenuItem
-                          #'label:' 'mono'
-                          #'argument:' 'mono'
-                          #'indication:' #'mode:value:'
-                      )
-                    ) nil
-                    nil
-                )
-            )
-             #(#MenuItem
-                #'label:' 'history'
-                #'enabled:' #hasHistory
-                #'submenuChannel:' #menuHistory
-            )
-             #(#MenuItem
-                #'label:' 'help'
-                #'submenuChannel:' #menuHelp
-            )
-          ) nil
-          nil
-      )
-
-! !
-
 !ImageEditView class methodsFor:'startup'!
 
 openOn:aFileName
@@ -303,46 +77,14 @@
 
 !ImageEditView methodsFor:'accessing'!
 
-checkModified
+coordInfoBlock: aBlock
 
-    modified
-    ifTrue:
-    [
-        |aBox|
-        aBox := YesNoBox title:'Image was modified'.        
-        aBox noText:'abort'.
-        aBox yesText:'ignore'.
-        aBox showAtPointer.
-        aBox accepted ifFalse: [^false].
-        modified := false
-    ].
-    ^true
+    coordInfoBlock := aBlock
 !
 
-gridMagnification
-
-    ^gridMagnification
-
-!
-
-gridMagnification:aPathName
-
-    gridMagnification := aPathName
-!
+gridMagnification: aPoint
 
-image:anImage
-
-    |oldMag|
-    (anImage isImage and: [image isNil or: [self checkModified]])
-    ifTrue:
-    [
-        oldMag := magnification.
-        magnification := 1@1.
-        super image: anImage.
-        self magnification:oldMag.
-        ^image
-    ].
-    ^nil
+    gridMagnification := aPoint
 !
 
 imageReaderClass
@@ -356,24 +98,537 @@
 
 !
 
-magnification:aMagnificationPoint
+magnification:aPoint
 
-    magnification ~= aMagnificationPoint
+    magnification ~= aPoint
     ifTrue:
     [
-        magnification := aMagnificationPoint asPoint.
+        magnification := aPoint asPoint.
         self scrollToTopLeft.
         self contentsChanged.
         self invalidate.
     ].
 !
 
-makeRedraw:aBooelean
+resourceClass
+
+    ^resourceClass
+!
+
+resourceClass: aClassOrSymbol
+
+    resourceClass := aClassOrSymbol isClass ifTrue: [aClassOrSymbol name] ifFalse: [aClassOrSymbol asSymbol].
+
+!
+
+resourceMessage
+
+    ^resourceClass, ' ', resourceSelector
+!
+
+resourceMessage: aMessage
+
+    (aMessage notNil and: [aMessage trimBlanks size > 0])
+    ifTrue:
+    [
+        resourceClass := aMessage readStream nextWord asSymbol.
+        resourceSelector := aMessage reversed readStream nextWord reverse asSymbol.
+    ]
+    ifFalse:
+    [
+        ^nil
+    ].
+
+    ^self resourceClass: resourceClass selector: resourceSelector
+
+   
+!
+
+resourceSelector
+
+    ^resourceSelector
+!
+
+resourceSelector: aStringOrSymbol
+
+    resourceSelector := aStringOrSymbol asSymbol
+!
+
+selectedColor
+
+   ^selectColors at: mouseKeyColorMode
+!
+
+selectedColor: aColor
+
+    selectColors at: mouseKeyColorMode put: aColor
+! !
+
+!ImageEditView methodsFor:'accessing menu'!
+
+menuEdit
+    "this window spec was automatically generated by the UI Builder"
+
+    ^ self class menuEdit
+
+
+! !
+
+!ImageEditView methodsFor:'drawing'!
+
+redrawImageX:x y:y width:w height:h
+    |ih iw dotW dotH minX maxX minY maxY color last lastY runW x0 xI yI maskColor|
+
+    ih := image height.
+    iw := image width.
+    dotW := magnification x.
+    dotH := magnification y.
+
+    minX := (x // dotW).
+    minX >= iw ifTrue:[minX := iw - 1].
+    minY := (y // dotH).
+    minY >= ih ifTrue:[minY := ih - 1].
+    maxX := (x + w) // dotW + 1.
+    maxX > iw ifTrue:[maxX := iw].
+    maxY := (y + h) // dotH + 1.
+    maxY > ih ifTrue:[maxY := ih].
+
+    lastY := -1.
+
+    x0 := minX.
+    runW := 0.
+    maskColor := false.
+    image colorsFromX:minX y:minY toX:maxX-1 y:maxY-1 do:
+    [:xx :yy :color|
+
+        yy ~~ lastY ifTrue:
+        [
+            runW ~~ 0 ifTrue:
+            [
+                |origin|
+                origin := (x0 * dotW + margin)@(lastY * dotH + margin).
+                self fillRectangle: (origin extent: (runW@dotH)).                    
+                0 to: runW by: dotW do: [:xxx| self drawFrameAt: ((origin x + xxx) @origin y)].
+                maskColor ifTrue:
+                [
+                    self drawMaskPointAt: origin
+                ].
+                runW := 0.
+            ]. 
+            x0 := xx.
+            lastY := yy.
+        ]. 
 
-    makeRedraw := aBooelean
+        color ~~ last ifTrue:
+        [
+            runW ~~ 0 ifTrue:
+            [
+                |origin|
+                origin := (x0 * dotW + margin)@(yy * dotH + margin).
+                self fillRectangle: (origin extent: (runW@dotH)).
+                0 to: runW by: dotW do: [:xxx| self drawFrameAt: ((origin x + xxx) @origin y)].
+                maskColor ifTrue:
+                [
+                    self drawMaskPointAt: origin
+                ].
+                runW := 0.
+            ].
+
+            self paint: (last := color).
+            image mask notNil ifTrue:
+            [  
+                maskColor := false.
+                (image mask colorAt: xx@yy) = Color black ifTrue:
+                [
+                    self paint: (last := self viewBackground).
+                    maskColor := true.
+                ].
+                last := nil.
+            ].
+            runW := 0.
+            x0 := xx.
+        ].  
+        runW := runW + dotW
+    ].
+    runW ~~ 0 ifTrue:
+    [
+        |origin|
+        origin := (x0 * dotW + margin)@(lastY * dotH + margin).
+        self fillRectangle: (origin extent: runW@dotH).
+        0 to: runW by: dotW do: [:xxx| self drawFrameAt: ((origin x + xxx) @origin y)].
+        maskColor ifTrue:
+        [
+            self drawMaskPointAt: origin.
+        ].
+        runW := 0.
+    ].
+!
+
+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 drawFrame.
+        ^ self
+    ].
+    self clippingRectangle: (x@y extent: w@h). 
+
+    self redrawImageX:x y:y width:w height:h.
+
+    "/ right of image ?
+    adjust == #center ifTrue:
+    [
+        xI := (width - (margin * 2) - ih) // 2.
+        yI := (height - (margin * 2) - iw) // 2.
+    ]
+    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.
+! !
+
+!ImageEditView methodsFor:'edit modes'!
+
+editMode
+
+    editMode isNil ifTrue: [editMode := 'point'].
+    ^editMode
+!
+
+editMode:aMode
+
+    editMode := aMode
+!
+
+mouseKeyColorMode
+
+    ^mouseKeyColorMode printString
+!
+
+mouseKeyColorMode:aMode
+
+    mouseKeyColorMode := aMode asInteger
+! !
+
+!ImageEditView methodsFor:'event handling'!
+
+buttonMotion:state x:x y:y
+
+    self selectedColor notNil & image notNil & (self imageContainsPoint: x@y) & (editMode = 'point')
+        ifTrue: [^self pointAt: x@y].
+
+    ^super buttonMotion:state x:x y:y
+
 !
 
-openFile: aFileName
+buttonPress:button x:x y:y
+
+    self selectedColor notNil & image notNil & (self imageContainsPoint: x@y)
+    ifTrue:
+    [   
+        undoImage := image copy.
+        mouseKeyColorMode := button.
+        (editMode = 'point')   ifTrue: [self pointAt: x@y].
+        (editMode = 'replace') ifTrue: [self replaceAt: x@y].
+        (editMode = 'paste')   ifTrue: [self pasteAt: x@y].
+        (editMode = 'box') | (editMode = 'copy') ifTrue: [self boxAt: x@y].
+        ^self
+    ].
+    
+    ^super buttonPress:button x:x y:y
+! !
+
+!ImageEditView methodsFor:'image drawing'!
+
+boxAt: aPoint
+
+    |firstPoint currentPoint lastCurrentPoint currentExtent imageFirstPoint imageExtent|
+
+    firstPoint := lastCurrentPoint := aPoint//magnification*magnification.
+    [Display anyButtonPressed]
+    whileTrue:
+    [   
+        currentPoint := (0@0) max: (image extent * magnification min: (self translation negated + (device translatePoint: self sensor mousePoint from:device rootView id to:self id))).
+        currentPoint := currentPoint//magnification*magnification.
+        currentExtent := (firstPoint - currentPoint) abs.
+        currentPoint ~= lastCurrentPoint ifTrue:
+        [
+            self redraw: ((firstPoint min: lastCurrentPoint) - 1 extent: (firstPoint - lastCurrentPoint) abs + 2).
+            editMode = 'copy'
+            ifTrue:
+            [
+                self xoring: [self fillRectangle: ((firstPoint min: currentPoint) + 1 extent: currentExtent - 1)]
+            ].
+            editMode = 'box'
+            ifTrue:
+            [
+                self selectedColor ~= Color noColor
+                    ifTrue: [self paint: self selectedColor]
+                    ifFalse: [self paint: self viewBackground].
+                self fillRectangle: ((firstPoint min: currentPoint) + 1 extent: currentExtent - 1)
+            ]. 
+        ]. 
+        self drawLabel: currentPoint//magnification.
+        lastCurrentPoint := currentPoint.
+    ].
+
+    imageFirstPoint := (firstPoint min: currentPoint)//magnification.
+    imageExtent := currentExtent//magnification.
+    editMode = 'box'
+    ifTrue:
+    [
+        self selectedColor ~= Color noColor
+        ifTrue:
+        [   
+            image mask notNil ifTrue: [image mask fillRectangleX: imageFirstPoint x y: imageFirstPoint y width: imageExtent x height: imageExtent y with:Color white].
+            image fillRectangleX: imageFirstPoint x y: imageFirstPoint y width: imageExtent x height: imageExtent y with: self selectedColor.
+            self paint: self selectedColor.
+        ] 
+        ifFalse:
+        [
+            image fillRectangleX: imageFirstPoint x y: imageFirstPoint y width: imageExtent x height: imageExtent y with: ((image colorMap includes: Color black) ifTrue: [Color black] ifFalse: [image colorMap first]).
+            image mask notNil ifTrue: [image mask fillRectangleX: imageFirstPoint x y: imageFirstPoint y width: imageExtent x height: imageExtent y with: Color black].
+            self paint: self viewBackground.
+        ].
+        image restored.
+        modified := true.
+    ].
+    editMode = 'copy'
+    ifTrue:
+    [      
+        Clipboard := image subImageIn: (imageFirstPoint extent: imageExtent - 1)
+    ].
+    self redraw: ((firstPoint min: currentPoint) - 1 extent: (firstPoint - currentPoint) abs + 2).    
+!
+
+pasteAt: aPoint
+
+    Object errorSignal handle:
+    [:ex|
+        WarningBox warn: 'Pasting into this image failed!!'.
+    ] 
+    do:
+    [   
+        |imagePoint|
+        imagePoint := aPoint//magnification.
+        image copyFrom: Clipboard x:0 y:0 toX: imagePoint x y: imagePoint y width: Clipboard width height: Clipboard height.
+        self redraw: (imagePoint * magnification extent: (Clipboard extent * magnification)).
+        self drawLabel: imagePoint.
+        image restored.
+        modified := true.
+    ]
+!
+
+pointAt: aPoint
+
+    |imagePoint|
+    imagePoint := aPoint//magnification.
+    self selectedColor ~= Color noColor
+    ifTrue:
+    [   
+        image mask notNil ifTrue: [image mask colorAt: imagePoint put: Color white].
+        image colorAt: imagePoint put: self selectedColor.
+        self paint: self selectedColor.
+    ] 
+    ifFalse:
+    [
+        image colorAt: imagePoint put: ((image colorMap includes: Color black) ifTrue: [Color black] ifFalse: [image colorMap first]).
+        image mask notNil ifTrue: [image mask colorAt: imagePoint put: Color black].
+        self paint:self viewBackground.
+    ].
+
+    self fillRectangle: (imagePoint * magnification + 1 extent: magnification).
+    self selectedColor = Color noColor
+    ifTrue:
+    [       
+        self drawMaskPointAt: imagePoint * magnification + 1.
+    ].
+    self drawFrameAt: aPoint.
+    self drawLabel: imagePoint.
+    image restored.
+    modified := true.
+!
+
+replaceAt: aPoint
+
+    |imagePoint|
+    imagePoint := aPoint//magnification.
+    self selectedColor ~= Color noColor
+    ifTrue:
+    [   
+        image mask notNil ifTrue: [image mask fillAround: imagePoint withColor: Color white].
+        image fillAround: imagePoint withColor: self selectedColor.
+        self paint: self selectedColor.
+    ] 
+    ifFalse:
+    [
+        image mask notNil ifTrue: [image mask fillAround: imagePoint withColor: Color black].
+        self paint:self viewBackground.
+    ].
+    self drawLabel: imagePoint.
+    self invalidate.
+    image restored.
+    modified := true.
+
+!
+
+undo
+
+    undoImage notNil
+    ifTrue:
+    [
+        modified := false.
+        self image: undoImage.
+        self invalidate
+    ]
+! !
+
+!ImageEditView methodsFor:'image editing'!
+
+flipHorizontal
+
+    self image: image flipHorizontal.
+
+!
+
+flipVertical
+
+    self image: image flipVertical.
+
+!
+
+negativeImage
+
+    self image: image negative.
+
+!
+
+resizeImage
+
+    |b newSize|
+
+    b := EnterBox new.
+    b title:'resize image'.
+    b okText:'apply'.
+    b abortText:'abort'.
+    b initialText:image extent printString.
+    b showAtPointer.
+    (newSize := Object readFromString: b contents onError:nil) notNil
+    ifTrue:
+    [
+        self image: (image magnifiedBy: newSize/image extent)
+    ].
+!
+
+rotateImage
+
+    |b rotation|
+
+    b := EnterBox new.
+    b title:'rotate image'.
+    b okText:'apply'.
+    b abortText:'abort'.
+    b initialText: '0'.
+    b showAtPointer.
+    (rotation := Object readFromString: b contents onError:nil) notNil
+    ifTrue:
+    [   Object errorSignal handle:
+        [:ex|
+            WarningBox warn: 'Image rotation failed.\' withCRs, 'An increase of image depth could help.'.
+        ] 
+        do:
+        [   
+            self image: (image hardRotated: rotation)
+        ]
+    ].
+! !
+
+!ImageEditView methodsFor:'image emphasis'!
+
+drawFrame
+
+    self paint:Color black.
+    "self lineWidth: (magnification x//3 min: 3). "
+    self displayRectangle: ((0@0) extent:(image extent * magnification) + 2).
+    self lineWidth:1.
+!
+
+drawFrameAt: aPoint
+
+    magnification > gridMagnification
+    ifTrue:
+    [   
+        |lineStartingPoint lineEndingPoint oldColor|
+        lineStartingPoint := aPoint//magnification*magnification.
+        lineEndingPoint   := aPoint//magnification*magnification + magnification.
+        oldColor := self paint.
+        self xoring:
+        [
+            self displayLineFrom: lineEndingPoint 
+                              to: (lineEndingPoint x)@(lineStartingPoint y).
+            self displayLineFrom: lineEndingPoint 
+                              to: (lineStartingPoint x)@(lineEndingPoint y).
+        ].
+        self paint: oldColor.
+    ]
+!
+
+drawLabel: aLabel
+    coordInfoBlock notNil
+    ifTrue:
+    [         
+        coordInfoBlock value: aLabel printString
+    ]
+!
+
+drawMaskPointAt: aPoint
+
+    |sizeOfMaskPoint|
+    sizeOfMaskPoint := magnification//3.
+    self xoring: [self fillRectangle: (aPoint + sizeOfMaskPoint extent: sizeOfMaskPoint)].
+   
+! !
+
+!ImageEditView methodsFor:'image setting'!
+
+image:anImage
+
+    (anImage isImage and: [image isNil or: [self checkModified]])
+    ifTrue:
+    [
+        super image: anImage.
+        image photometric = #palette
+        ifTrue:
+        [
+            (image usedColors includes: selectColors first) ifFalse: [selectColors at: 1 put: nil].
+            (image usedColors includes: selectColors last) ifFalse: [selectColors at: 2 put: nil].
+        ].
+        ^self
+    ].
+    ^nil
+!
+
+loadFromFile: aFileName
 
     |fileName newImage|
     fileName := aFileName asFilename.
@@ -396,409 +651,19 @@
     ]
 !
 
-pixelSelectColor: aColor
-
-    pixelSelectColor := aColor
-!
-
-resourceClass
-
-    ^resourceClass
-!
-
-resourceClass: aClass
-
-    resourceClass := aClass
-!
+resourceClass: aClassOrSymbol selector: aStringOrSymbol
 
-resourceClass: aClass selector: aSelector
-
-    resourceClass := aClass.
-    resourceSelector := aSelector.
-    (aClass isClass and: [aClass class implements: aSelector])
-    ifTrue:
-    [   
-        ^self image: (aClass perform: aSelector)
-    ].
-    ^nil
-!
-
-resourceMessage
-
-    (resourceClass value notNil and: [resourceSelector value notNil])
+    |aClass|
+    imageReaderClass := nil.
+    self resourceClass: aClassOrSymbol.
+    self resourceSelector: aStringOrSymbol.
+    aClass := Smalltalk at: resourceClass. 
+    (aClass isClass and: [aClass class implements: resourceSelector])
     ifTrue:
     [ 
-        ^resourceClass name, ' ', resourceSelector
+        ^self image: (aClass perform: resourceSelector) copy
     ].
     ^nil
-!
-
-resourceMessage: aMessage
-
-    aMessage isNil ifTrue: [^nil].
-    resourceClass := Smalltalk at: aMessage copy readStream nextWord asSymbol.
-    resourceSelector := aMessage copy reverse readStream nextWord reverse asSymbol.
-
-    ^self resourceClass: resourceClass selector: resourceSelector
-
-   
-!
-
-resourceSelector
-
-    ^resourceSelector
-!
-
-resourceSelector: aSelector
-
-    resourceSelector := aSelector
-! !
-
-!ImageEditView methodsFor:'accessing menu'!
-
-menuEffects
-    "this window spec was automatically generated by the UI Builder"
-
-    ^ self class menuEffects
-
-
-! !
-
-!ImageEditView methodsFor:'drawing'!
-
-colorAt: aPoint put: aColor
-
-    |tempPaint|
-    tempPaint := self paint.
-    aColor redByte = 'mask'
-    ifTrue:
-    [       
-        image restored; colorAt: aPoint//magnification put: Color black.
-        image mask notNil ifTrue: [image mask restored; colorAt: aPoint//magnification put: Color black].
-        self paint:Color lightGray.
-    ]
-    ifFalse:
-    [
-        image mask notNil ifTrue: [image mask restored; colorAt: aPoint//magnification put: Color white].
-        image restored; colorAt: aPoint//magnification put: aColor.
-        self paint:aColor.
-    ].
-
-    self fillRectangleX:(aPoint x // magnification x) * magnification x + 1
-        y:(aPoint y // magnification y) * magnification y + 1
-        width:magnification x  height:magnification y.
-
-    self paint:tempPaint.
-    magnification > gridMagnification
-    ifTrue:
-    [
-        self drawGridMagnification
-    ].
-
-!
-
-drawGridMagnification
-
-    |tempPaint|
-    tempPaint := self paint.
-    self paint:Color black.
-    0 to: (image width * magnification x) by: magnification x do:
-    [:x|
-        self displayLineFromX:x y:0 toX:x y:(image height * magnification y)
-    ].
-    0 to: (image height * magnification y) by: magnification y do:
-    [:y|
-        self displayLineFromX:0 y:y toX:(image width * magnification x) y:y
-    ].
-    self paint:tempPaint.
-!
-
-redrawImageX:x y:y width:w height:h
-    |ih iw dotW dotH minX maxX minY maxY color last lastY runW x0 xI yI|
-
-    ih := image height.
-    iw := image width.
-    dotW := magnification x.
-    dotH := magnification y.
-
-    minX := (x // dotW).
-    minX > iw ifTrue:[
-        minX := iw - 1
-    ].
-
-    minY := (y // dotH) .
-    minY > ih ifTrue:[
-        minY := ih - 1
-    ].
-    maxX := (x + w) // dotW + 1.
-    maxX > iw ifTrue:[
-        maxX := iw
-    ].
-    maxY := (y + h) // dotH + 1.
-    maxY > ih ifTrue:[ 
-        maxY := ih
-    ].
-
-    lastY := -1.
-
-    x0 := minX.
-    runW := 0.
-
-    image colorsFromX:minX y:minY toX:maxX-1 y:maxY-1 do:[:xx :yy :color |
-
-        yy ~~ lastY ifTrue:[
-            runW ~~ 0 ifTrue:[
-                self fillRectangleX:(x0 * dotW + margin)
-                                  y:(lastY * dotH + margin)
-                              width:runW height:dotH.
-                runW := 0.
-            ]. 
-            x0 := xx.
-            lastY := yy.
-        ]. 
-
-        color ~~ last ifTrue:[
-            runW ~~ 0 ifTrue:[
-                self fillRectangleX:(x0 * dotW + margin)
-                                  y:(yy * dotH + margin)
-                              width:runW height:dotH.
-                runW := 0.
-            ].
-
-            "self paint:color."
-            (image mask notNil and: [(image mask colorAt: xx@yy) = Color black])
-                ifTrue: [self paint: Color lightGray] ifFalse: [self paint: color].
-            last := color.
-            runW := 0.
-            x0 := xx.
-        ].  
-        runW := runW + dotW
-    ].
-    runW ~~ 0 ifTrue:[
-        self fillRectangleX:(x0 * dotW + margin)
-                          y:(lastY * dotH + margin)
-                      width:runW height:dotH.
-        runW := 0.
-    ].
-!
-
-redrawX:x y:y width:w height:h
-    |ih iw dotW dotH minX maxX minY maxY color last lastY runW x0 xI yI|
-
-    image isNil ifTrue:[^self].
-
-    magnification = (1@1) ifTrue:[
-        super redrawX:x y:y width:w height:h.
-        ^ self
-    ].
-    self clippingRectangle: (x@y extent: w@h). 
-
-    self redrawImageX:x y:y width:w height:h.
-
-    "/ right of image ?
-    adjust == #center ifTrue:[
-            xI := (width - (margin * 2) - ih) // 2.
-            yI := (height - (margin * 2) - iw) // 2.
-        ] 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)  
-    ].
-    magnification > gridMagnification
-    ifTrue:
-    [
-        self drawGridMagnification
-    ].
-    self clippingRectangle: nil
-! !
-
-!ImageEditView methodsFor:'event handling'!
-
-buttonMotion:state x:x y:y
-
-    self showColorAtX:x y:y.
-!
-
-buttonMultiPress:button x:x y:y
-    button == 1 ifTrue:[
-        |clr|
-        clr := self getColorAtX:x y:y.
-    ].
-    super buttonMultiPress:button x:x y:y
-
-    "Created: 8.5.1996 / 00:18:06 / stefan"
-!
-
-buttonPress:button x:x y:y
-    button == 1 ifTrue:[
-        self showColorAtX:x y:y.
-        ^ self
-    ].
-    super buttonPress:button x:x y:y
-!
-
-getColorAtX:x y:y
-    |pi|
-
-    pi := (((x @ y) - margin + 1) / magnification)  floor.
-    ((0@0 corner:(image extent) - 1) containsPoint:pi)
-    ifTrue:
-    [
-        ^ image at:pi
-    ].
-    ^ nil
-
-    "Created: 8.5.1996 / 00:15:55 / stefan"
-!
-
-showColorAtX:x y:y
-    |clr|
-
-    clr := self getColorAtX:x y:y.
-    clr notNil
-    ifTrue:
-    [
-        pixelSelectColor isColor" & (image colorMap includes: clr)"
-        ifTrue:
-        [   
-            makeRedraw ifTrue: [self invalidate. makeRedraw := false].
-            modified := true.
-            self colorAt: x@y put: pixelSelectColor.
-        ]
-    ]
-! !
-
-!ImageEditView methodsFor:'image conversion'!
-
-convertToColor24
-    (Depth24Image fromImage:image) inspect
-
-    "Modified: 3.6.1997 / 18:34:34 / cg"
-!
-
-convertToColor4
-    (Depth4Image fromImage:image) inspect
-
-    "Modified: 3.6.1997 / 18:34:45 / cg"
-!
-
-convertToColor8
-    (Depth8Image fromImage:image) inspect
-
-    "Created: 3.6.1997 / 18:34:08 / cg"
-    "Modified: 3.6.1997 / 18:34:51 / cg"
-!
-
-convertToGray2
-    (image asFloydSteinbergDitheredGrayImageDepth:2) inspect
-
-    "Created: 3.6.1997 / 18:34:02 / cg"
-    "Modified: 3.6.1997 / 18:39:23 / cg"
-!
-
-convertToGray4
-    (image asFloydSteinbergDitheredGrayImageDepth:4) inspect
-
-    "Created: 3.6.1997 / 18:34:04 / cg"
-    "Modified: 3.6.1997 / 18:39:20 / cg"
-!
-
-convertToGray8
-    (image asFloydSteinbergDitheredGrayImageDepth:8) inspect
-
-    "Created: 3.6.1997 / 18:34:05 / cg"
-    "Modified: 3.6.1997 / 18:39:16 / cg"
-!
-
-convertToMono
-    (image asFloydSteinbergDitheredGrayImageDepth:1) inspect
-
-    "Created: 3.6.1997 / 18:33:42 / cg"
-    "Modified: 3.6.1997 / 18:39:26 / cg"
-! !
-
-!ImageEditView methodsFor:'image processing'!
-
-flipHorizontal
-    self performImageOperation:#flipHorizontal withArguments:nil
-!
-
-flipVertical
-    self performImageOperation:#flipVertical withArguments:nil
-!
-
-negative
-    self performImageOperation:#negative withArguments:nil 
-!
-
-performImageOperation:operation withArguments:args
-    |oldMag newImage|
-
-    windowGroup withCursor:Cursor wait do:[
-        oldMag := magnification.
-        magnification := 1@1.
-        newImage := image perform:operation withArguments:args.
-        newImage isNil ifTrue:[
-            self information:'conversion failed - revert to original'.
-            ^ self
-        ].
-        image := newImage.
-        self clear.
-        (oldMag isNil or:[oldMag = magnification]) ifTrue:[
-            self invalidate
-        ] ifFalse:[
-            self magnification:oldMag.
-        ]
-    ]
-
-    "Modified: 23.6.1997 / 09:49:26 / cg"
-!
-
-resizeImage
-    |b newSize newImage wNew hNew bits|
-
-    b := EnterBox new.
-    b title:'new size (x @ y) contents will be located at top-left'.
-    b okText:'apply'.
-    b abortText:'abort'.
-    b action:[:string | newSize := Object readFromString:string onError:nil].
-    b initialText:(image extent printString).
-    b showAtPointer.
-
-    newSize notNil ifTrue:[
-        wNew := image width min:newSize x.
-        hNew := image height min:newSize y.
-
-        newImage := Image 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)).
-
-        newImage copyFrom:image x:0 y:0 toX:0 y:0 width:wNew height:hNew.
-
-        self image: newImage
-    ].
-
-    "Created: 31.7.1997 / 11:41:14 / cg"
-    "Modified: 31.7.1997 / 13:45:47 / cg"
-!
-
-rotateCCW
-    self performImageOperation:#rotated: withArguments:#(270)
-!
-
-rotateCW
-    self performImageOperation:#rotated: withArguments:#(90)
 ! !
 
 !ImageEditView methodsFor:'initialization'!
@@ -806,197 +671,14 @@
 initialize
 
     super initialize.
+
     magnification := 1@1.
-    gridMagnification := 5@5.
-    makeRedraw := modified := antiAlias := false.
-
-    self menuHolder:self; menuPerformer:self; menuMessage:#imageMenu.
-
-    "Modified: 2.6.1997 / 15:49:00 / cg"
-! !
-
-!ImageEditView methodsFor:'menu'!
-
-imageMenu
-    |m convertMenu labels selectors|
-
-    image mask notNil ifTrue:[
-        labels := #(
-                        'save as ...'
-                        'save mask as ...'
-                       ).
-        selectors := #(
-                        saveAs
-                        saveMaskAs
-                      ).
-        magnification ~~ (1@1) notNil ifTrue:[
-            labels := labels , #(
-                        '-'
-                        'save magnified as ...'
-                        'save magnified mask as ...'
-                       ).
-
-            selectors := selectors , #(
-                        nil
-                        saveMagnifiedAs
-                        saveMagnifiedMaskAs
-                      ).
-        ]
-    ] ifFalse:[
-        labels := #(
-                        'save as ...'
-                       ).
-        selectors := #(
-                        saveAs
-                      ).
-        magnification ~~ (1@1) ifTrue:[
-            labels := labels , #(
-                        '-'
-                        'save magnified as ...'
-                       ).
-
-            selectors := selectors , #(
-                        nil
-                        saveMagnifiedAs
-                      ).
-        ]
-    ].
-
-    labels := labels , #(
-                            '-'
-                            'print'
-                            'print magnified'
-                            '-'
-                            'magnification'
-                            'magnify & antiAlias'
-"/                            'colors'
-                            'effects'
-                            'convert to'
-                        ).
-    selectors := selectors , #(
-                        nil
-                        doPrint
-                        doPrintMagnified
-                        nil
-                        changeMagnification
-                        changeMagnificationAndAntiAlias
-"/                        showColors
-                        effects
-                        convert
-                        ).
-
-    m := PopUpMenu
-               labels:(resources array:labels)
-            selectors:selectors
-             receiver:self
-                  for:self.
-
-    magnification = 1 ifTrue:[
-        m disable:#doPrintMagnified
-    ].
-
-    m subMenuAt:#effects put:(
-        PopUpMenu labels:(resources array:#(
-                            'flip - vertical'
-                            'flip - horizontal'
-                            '-'
-                            'rotate - clockwise'
-                            'rotate - counter clockwise'
-                            '-'
-                            'negative'
-                            '-'
-                            'resize'
-"
-                            'blurr'
-"
-                           ))
-               selectors:#(
-                            flipVertical
-                            flipHorizontal
-                            nil
-                            rotateCW
-                            rotateCCW
-                            nil
-                            negative
-                            nil
-                            resizeImage
-"
-                            blurr
-"
-                           )
-                receiver:self
-                     for:self
-
-    ).
-
-    m subMenuAt:#convert put:(
-        convertMenu :=
-        PopUpMenu labels:(resources array:#(
-                            'monochrome (dither)'
-                            '-'
-                            'gray 2-plane (dither)'
-                            'gray 4-plane (dither) '
-                            'gray 8-plane '
-                            '-'
-"/                            'color 4-plane (dither)'
-"/                            'color 8-plane (dither)'
-                            'color 24-plane'
-                           ))
-               selectors:#(
-                            convertToMono
-                            nil
-                            convertToGray2
-                            convertToGray4
-                            convertToGray8
-                            nil
-"/                            convertToColor4
-"/                            convertToColor8
-                            convertToColor24
-                           )
-                receiver:self
-                     for:self
-    ).
-
-    image depth == 1 ifTrue:[
-        convertMenu disable:#convertToMono
-    ].
-    image depth == 2 ifTrue:[
-        (image photometric ~~ #palette
-        and:[image photometric ~~ #rgb]) ifTrue:[
-            convertMenu disable:#convertToGray2
-        ]
-    ].
-    image depth == 4 ifTrue:[
-        (image photometric ~~ #palette
-        and:[image photometric ~~ #rgb]) ifTrue:[
-            convertMenu disable:#convertToGray4
-        ] ifFalse:[
-            convertMenu disable:#convertToColor4
-        ]
-    ].
-    image depth == 8 ifTrue:[
-        (image photometric ~~ #palette
-        and:[image photometric ~~ #rgb]) ifTrue:[
-            convertMenu disable:#convertToGray8
-        ] ifFalse:[
-            convertMenu disable:#convertToColor8
-        ]
-    ].
-    image depth == 24 ifTrue:[
-        image photometric == #rgb ifTrue:[
-            convertMenu disable:#convertToColor24
-        ]
-    ].
-
-    ^ m
-
-    "
-     ImageEditView openOn:'bitmaps/SBrowser.xbm'
-     ImageEditView openOn:'bitmaps/garfield.gif'
-    "
-
-    "Created: 20.2.1997 / 18:47:17 / cg"
-    "Modified: 31.7.1997 / 11:41:26 / cg"
+    gridMagnification := 8@8.
+    modified := false.
+    mouseKeyColorMode := 1.
+    resourceClass := resourceSelector := ''.
+    selectColors := Array with: nil with: nil.
+    self menuHolder:self; menuPerformer:self; menuMessage:#imageMenu. 
 ! !
 
 !ImageEditView methodsFor:'menu actions'!
@@ -1013,81 +695,35 @@
     b showAtPointer.
 
     newMag notNil ifTrue:[
-        antiAlias ifTrue:[
-            magnification := nil.
-        ].
-        antiAlias := false.
         self magnification:newMag.
     ].
 
     "Modified: 31.7.1997 / 11:43:12 / cg"
 !
 
-changeMagnificationAndAntiAlias
-    |b newMag|
-
-    b := EnterBox new.
-    b title:'magnification (magX @ magY)'.
-    b okText:'apply'.
-    b abortText:'abort'.
-    b action:[:string | newMag := (Object readFromString:string onError:nil)].
-    b initialText:(magnification printString).
-    b showAtPointer.
+loadFromClass
 
-    newMag notNil ifTrue:[
-        antiAlias ifFalse:[
-            magnification := nil.
-        ].
-        antiAlias := true.
-        self magnification:newMag
-    ].
+    self resourceMessage: (ResourceBrowserView
+        openOnSuperclass: ApplicationModel
+        class: self resourceClass
+        selector: self resourceSelector
+        resourceTypes: #(#image #fileImage))
+        
 
-    "Created: 2.6.1997 / 15:51:01 / cg"
-    "Modified: 31.7.1997 / 11:43:47 / cg"
 !
 
-createFileName
+loadFromUser
 
-    image fileName notNil
-    ifFalse:
-    [   
-        |fileName|
-        (fileName := FileBrowserView requestFileName) notNil
-        ifTrue:
-        [    self halt.
-            image fileName: fileName.
-            ^true
-        ].
-    ].
-    ^true.
+    self image: 
+        ((Image fromUser)
+            asDitheredTrueColor8FormOn: Display)
+
 !
 
-createResourceMessage
+print
+    |stream psgc|
 
-    (self resourceClass class implements: self resourceSelector)
-    ifFalse:
-    [   
-        ((ResourceBrowserView
-            openOnSuperclass: #ApplicationModel
-            class: resourceClass
-            selector: resourceSelector
-            resourceTypes: #(#image #fileImage))) notNil
-        ifTrue:
-        [
-            ^true
-        ].
-    ].
-    ^false.
-!
-
-doPrint
-    self doPrint:image
-
-    "Modified: 2.6.1997 / 18:32:11 / cg"
-!
-
-doPrint:anImage
-    |stream psgc|
+    image isNil ifTrue: [^nil].
 
     Printer supportsPostscript ifFalse:[
         self warn:'need a postscript printer'.
@@ -1102,131 +738,32 @@
 
     self withWaitCursorDo:[
         psgc := PSGraphicsContext on:stream. "/  extent:(1.0 @ 1.0).
-        psgc displayForm:anImage x:0 y:0.
+        psgc displayForm: (image magnifiedBy: magnification) x:0 y:0.
         psgc close.
     ]
-
-    "Modified: 28.5.1997 / 10:54:11 / cg"
-    "Created: 2.6.1997 / 18:32:03 / cg"
-!
-
-doPrintMagnified
-    "self doPrint:(magnifiedImage ? image)"
-
-    "Modified: 2.6.1997 / 18:31:54 / cg"
-!
-
-doSaveImageAs:anImage title:aTitle
-    "save contents into a file 
-     - ask user for filename using a fileSelectionBox."
-
-    |fileName imgFileName defaultName rdr i txt suffix|
-
-    defaultName := pathName ? ''.
-
-    pathName isNil ifTrue:[
-        suffix := 'tiff'.
-        (imgFileName := image fileName) notNil ifTrue:[
-            suffix := imgFileName asFilename suffix.
-            defaultName := imgFileName asFilename baseName
-        ]
-    ] ifFalse:[
-        suffix := pathName asFilename suffix.
-        "/ a supported suffix ?
-        ((rdr := Image imageReaderClassForSuffix:suffix) isNil 
-        or:[(rdr canRepresent:anImage) not]) ifTrue:[
-            suffix := 'tiff'.
-            defaultName := (pathName asFilename withSuffix:suffix) pathName
-        ].
-    ].
-
-    Image cannotRepresentImageSignal handle:[:ex |
-        self warn:('cannot represent this image in that format.\\(%1)' bindWith:ex errorString) withCRs.
-        fileName := nil.
-        ex restart
-    ] do:[
-        fileName := Dialog
-                        requestFileName:(resources string:aTitle)
-                        default:defaultName
-                        ok:(resources string:'save')
-                        abort:(resources string:'abort')
-                        pattern:('*.' , suffix).
-
-        fileName notNil ifTrue:[
-            anImage saveOn:fileName.
-        ].
-    ].
-    pathName := fileName.
-
-    "Created: / 20.2.1997 / 18:52:08 / cg"
-    "Modified: / 3.11.1997 / 15:02:27 / cg"
-!
-
-generateFileAccess
-
-    self createFileName
-    ifTrue:
-    [
-        |compileString stream|
-        stream := WriteStream on: ''.
-        self image storeOn: stream.
-        compileString :=
-            self resourceSelector,
-            '\\' withCRs,
-            '    <resource: #fileImage>\' withCRs,
-            '    ^Image fromFile:''',
-            image fileName, ''''.
-        ByteCodeCompiler compile: compileString forClass: self resourceClass class inCategory: 'image specs'.
-    ]
-!
-
-generateImage
-
-    "self createResourceMessage
-    ifTrue:
-    ["
-        |compileString stream|  
-        stream := WriteStream on: ''.
-        self image storeOn: stream.
-        compileString :=
-            self resourceSelector,
-            '\\' withCRs,
-            '    <resource: #image>\' withCRs,
-            '    ^',
-            stream contents.   
-        ByteCodeCompiler compile: compileString forClass: self resourceClass class inCategory: 'image specs'.
-    "]"   
-!
-
-loadFromClass
-
-    self resourceMessage: (ResourceBrowserView
-        openOnSuperclass: ApplicationModel
-        class: self resourceClass
-        selector: self resourceSelector
-        resourceTypes: #(#image #fileImage))
-        
-
 !
 
 save
 
-    |fileName|
-    fileName := image fileName.
     Object errorSignal handle:
-    [:exeption|
-        WarningBox warn: exeption errorString.
-        ^nil
+    [:ex|
+        WarningBox warn: ex errorString.
+        ^nil                                 
     ] 
     do:
-    [
+    [   
+        |fileName|
+        image isNil ifTrue: [^self error: 'No image to save!!'].
+        image fileName isNil ifTrue: [^self error: 'No file name for image detected!!'].
+        fileName := image fileName asFilename.
         (fileName suffix = 'tiff') | (fileName suffix = 'tif') ifTrue: [imageReaderClass := TIFFReader].
         fileName suffix = 'xpm' ifTrue: [imageReaderClass := XPMReader].
         fileName suffix = 'xbm' ifTrue: [imageReaderClass := XBMReader].
         fileName suffix = 'gif' ifTrue: [imageReaderClass := GIFReader].
         (fileName suffix = 'jpg') | (fileName suffix = 'jpeg') ifTrue: [imageReaderClass := JPEGReader].
-        imageReaderClass isNil ifTrue: [^self error: 'no appropriate image reader found'].
-        image saveOn: fileName using: imageReaderClass.
+        imageReaderClass isNil ifTrue: [imageReaderClass := XPMReader. image fileName: image fileName, '.xpm'].
+        
+        image saveOn: image fileName using: imageReaderClass.
         modified := false.
     ]
        
@@ -1236,42 +773,76 @@
     "save contents into a file 
      - ask user for filename using a fileSelectionBox."
 
-    self doSaveImageAs:image title:'save image in:'
-
-    "Modified: 20.2.1997 / 18:52:37 / cg"
-!
-
-saveMagnifiedAs
-    "save contents into a file 
-     - ask user for filename using a fileSelectionBox."
-
-    "self doSaveImageAs:magnifiedImage title:'save magnified image in:' "
-
-    "Created: 20.2.1997 / 18:52:53 / cg"
+    self saveImageFileAs
 !
 
-saveMagnifiedMaskAs
-    "save contents into a file 
-     - ask user for filename using a fileSelectionBox."
+saveAsMethod
 
-    "self doSaveImageAs:(magnifiedImage mask) title:'save magnified mask in:'"
-
-    "Created: 20.2.1997 / 18:53:31 / cg"
-    "Modified: 20.2.1997 / 18:56:48 / cg"
+    Object errorSignal handle:
+    [:ex|
+        WarningBox warn: ex errorString.
+        ^nil                                 
+    ] 
+    do:
+    [   
+        |compileString stream aClass|  
+        stream := WriteStream on: ''.
+        self resourceSelector trimBlanks size = 0 ifTrue: [^self error: 'No image selector detected'].
+        (aClass := Smalltalk at: self resourceClass) isClass ifFalse: [^self error: 'No class for image selector detected'].
+        self image storeOn: stream.
+        compileString :=
+            self resourceSelector,
+            '\\' withCRs,
+            '    <resource: #image>\' withCRs,
+            '    ^',
+            stream contents.   
+        ByteCodeCompiler compile: compileString forClass: aClass class inCategory: 'resources'.
+        modified := false.
+    ]
 !
 
-saveMaskAs
-    "save contents into a file 
-     - ask user for filename using a fileSelectionBox."
+saveImageFileAs
+
+    |aFileName|
+
+    (aFileName := (FileBrowserView requestFileName: self image fileName fileFilters: #('*.xpm' '*.gif'))) notNil
+    ifTrue:
+    [
+        self saveImageFileAs: aFileName
+    ].
+!
 
-    self doSaveImageAs:(image mask) title:'save mask in:'
+saveImageFileAs: aFileName
 
-    "Created: 20.2.1997 / 18:51:06 / cg"
-    "Modified: 20.2.1997 / 18:56:54 / cg"
+    image notNil
+    ifTrue:
+    [
+        image fileName: aFileName.
+        self save
+    ]
+    ifFalse:
+    [
+        WarningBox warn: 'No image detected'
+    ]
 ! !
 
 !ImageEditView methodsFor:'queries'!
 
+checkModified
+
+    modified ifTrue:
+    [
+        |aBox|
+        aBox := YesNoBox title:'Image was modified'.        
+        aBox noText:'abort'.
+        aBox yesText:'ignore'.
+        aBox showAtPointer.
+        aBox accepted ifFalse: [^false].
+        modified := false
+    ].
+    ^true
+!
+
 heightOfContents
     "return the images height"
 
@@ -1279,6 +850,13 @@
     ^ (image height * magnification y) rounded
 !
 
+imageContainsPoint: aPoint
+    |pi|
+    image isNil ifTrue: [^false].
+    pi := ((aPoint - margin + 1) / magnification) floor.
+    ^((0@0 corner:(image extent) - 1) containsPoint:pi)
+!
+
 widthOfContents
     "return the images width"
 
@@ -1286,8 +864,18 @@
     ^ (image width * magnification x) rounded
 ! !
 
+!ImageEditView methodsFor:'release'!
+
+destroy
+
+    undoImage := nil.
+    Clipboard := nil.
+    super destroy.
+
+! !
+
 !ImageEditView class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libwidg2/Attic/ImgEditV.st,v 1.48 1997-11-26 18:53:45 tz Exp $'
+    ^ '$Header: /cvs/stx/stx/libwidg2/Attic/ImgEditV.st,v 1.49 1997-12-03 13:34:40 tz Exp $'
 ! !