revised version
authortz
Thu, 11 Dec 1997 13:43:42 +0100
changeset 633 594edef86630
parent 632 be1ac8ea33a7
child 634 cee0d1f706e1
revised version
ImageEditView.st
ImgEditV.st
--- a/ImageEditView.st	Mon Dec 08 21:25:10 1997 +0100
+++ b/ImageEditView.st	Thu Dec 11 13:43:42 1997 +0100
@@ -61,19 +61,17 @@
 
 resourceMessage: aMessage
 
-    (aMessage notNil and: [aMessage trimBlanks size > 0])
+    (aMessage isString and: [aMessage trimBlanks size > 0])
     ifTrue:
     [
-        resourceClass := aMessage readStream nextWord asSymbol.
-        resourceSelector := aMessage reversed readStream nextWord reverse asSymbol.
+        resourceClass := (aMessage readStream upTo: Character space) asSymbol.
+        resourceSelector := (aMessage copy reverse readStream upTo: Character space) reverse asSymbol.
     ]
     ifFalse:
     [
         ^nil
     ].
 
-    ^self resourceClass: resourceClass selector: resourceSelector
-
    
 !
 
@@ -87,9 +85,14 @@
     resourceSelector := aStringOrSymbol asSymbol
 !
 
+selectColor: anArrayTwoColors
+
+    selectColors := anArrayTwoColors
+!
+
 selectedColor
 
-   ^(selectColors at: mouseKeyColorMode) ? Color black
+   ^selectColors at: mouseKeyColorMode
 !
 
 selectedColor: aColor
@@ -107,9 +110,9 @@
     dotW := magnification x.
     dotH := magnification y.
 
-    minX := (x // dotW).
+    minX := x // dotW.
     minX >= iw ifTrue:[minX := iw - 1].
-    minY := (y // dotH).
+    minY := y // dotH.
     minY >= ih ifTrue:[minY := ih - 1].
     maxX := (x + w) // dotW + 1.
     maxX > iw ifTrue:[maxX := iw].
@@ -123,10 +126,11 @@
     maskColor := false.
     image colorsFromX:minX y:minY toX:maxX-1 y:maxY-1 do:
     [:xx :yy :color|
-
-        yy ~~ lastY ifTrue:
+        yy ~~ lastY
+        ifTrue:
         [
-            runW ~~ 0 ifTrue:
+            runW ~~ 0
+            ifTrue:
             [
                 |origin|
                 origin := (x0 * dotW + margin)@(lastY * dotH + margin).
@@ -142,9 +146,11 @@
             lastY := yy.
         ]. 
 
-        color ~~ last ifTrue:
+        color ~~ last
+        ifTrue:
         [
-            runW ~~ 0 ifTrue:
+            runW ~~ 0
+            ifTrue:
             [
                 |origin|
                 origin := (x0 * dotW + margin)@(yy * dotH + margin).
@@ -192,12 +198,6 @@
 
     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.
@@ -205,8 +205,8 @@
     "/ right of image ?
     adjust == #center ifTrue:
     [
-        xI := (width - (margin * 2) - ih) // 2.
-        yI := (height - (margin * 2) - iw) // 2.
+        xI := (width - ih) // 2 - margin.
+        yI := (height - iw) // 2 - margin.
     ]
     ifFalse:
     [
@@ -307,10 +307,10 @@
         |filledPoints|
         filledPoints := image floodFillAt: aPoint//magnification withColor: self selectedColor.
         image restored.
-        filledPoints size < 100
+        filledPoints size < 300
         ifTrue:
         [
-            filledPoints do: [:p| Delay waitForMilliseconds:1. self redraw: ((p * magnification extent: magnification) expandedBy: 1@1)]
+            filledPoints do: [:p| Delay waitForMilliseconds:0.7. self redraw: ((p * magnification extent: magnification) expandedBy: 1@1)]
         ]
         ifFalse:
         [
@@ -332,8 +332,9 @@
 
 getRectangleFrom: aPoint emphasis: emphasis
 
-    |currentPoint currentExtent firstPoint lastCurrentPoint p|
+    |currentPoint currentExtent firstPoint lastCurrentPoint gridCorrection p|
     firstPoint := currentPoint := lastCurrentPoint := aPoint//magnification*magnification.
+    self isGridOn ifFalse: [gridCorrection := 0] ifTrue: [gridCorrection := 1].
     [Display anyButtonPressed]
     whileTrue:
     [   
@@ -348,7 +349,7 @@
             emphasis = #inverseFilledBox
             ifTrue:
             [
-                self xoring: [self fillRectangle: ((firstPoint min: currentPoint) + 1 extent: currentExtent - 1)]
+                self xoring: [self fillRectangle: ((firstPoint min: currentPoint) + 1 extent: currentExtent - gridCorrection)]
             ].
             emphasis = #box
             ifTrue:
@@ -357,7 +358,7 @@
                     ifTrue: [self paint: self selectedColor]
                     ifFalse: [self paint: self viewBackground].
                 self lineWidth: magnification x.
-                self displayRectangle: ((firstPoint min: currentPoint) + (magnification x//2) extent: (currentExtent - (magnification x))).
+                self displayRectangle: ((firstPoint min: currentPoint) + (magnification x//2) + 1 extent: (currentExtent - (magnification x)) - gridCorrection + 1).
                 self lineWidth: 1.
             ].
             emphasis = #filledBox
@@ -366,8 +367,7 @@
                 self selectedColor ~= Color noColor
                     ifTrue: [self paint: self selectedColor]
                     ifFalse: [self paint: self viewBackground].
-                self fillRectangle: ((firstPoint min: currentPoint) extent: currentExtent).
-                self displayRectangle: ((firstPoint min: currentPoint) extent: currentExtent).
+                self fillRectangle: ((firstPoint min: currentPoint) + 1 extent: currentExtent - gridCorrection).
             ].
         ]. 
         self drawLabel: currentPoint//magnification.
@@ -381,7 +381,7 @@
 
     Object errorSignal handle:
     [:ex|
-        WarningBox warn: 'Pasting into this image failed!!'.
+        self warn: 'Pasting at selected point failed!!'.
     ] 
     do:
     [   
@@ -443,12 +443,12 @@
     |b newSize|
 
     b := EnterBox new.
-    b title:'resize image'.
-    b okText:'apply'.
-    b abortText:'abort'.
+    b title:'Image new size:'.
+    b okText:'OK'.
+    b abortText:'Cancel'.
     b initialText:image extent printString.
     b showAtPointer.
-    (newSize := Object readFromString: b contents onError:nil) notNil
+    (b accepted and: [(newSize := Object readFromString: b contents onError:nil) notNil])
     ifTrue:
     [
         self image: (image magnifiedBy: newSize/image extent)
@@ -460,16 +460,16 @@
     |b rotation|
 
     b := EnterBox new.
-    b title:'rotate image'.
-    b okText:'apply'.
-    b abortText:'abort'.
+    b title:'Image new rotation:'.
+    b okText:'OK'.
+    b abortText:'Cancel'.
     b initialText: '0'.
     b showAtPointer.
-    (rotation := Object readFromString: b contents onError:nil) notNil
+    (b accepted and: [(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.'.
+            self warn: 'Image rotation failed.\' withCRs, 'An increase of image depth could help.'.
         ] 
         do:
         [   
@@ -499,7 +499,7 @@
 
 drawFrameAt: aPoint
 
-    magnification > gridMagnification
+    self isGridOn
     ifTrue:
     [   
         |lineStartingPoint lineEndingPoint oldColor|
@@ -518,6 +518,7 @@
 !
 
 drawLabel: aLabel
+
     coordInfoBlock notNil
     ifTrue:
     [         
@@ -554,7 +555,7 @@
         ^nil
     ] 
     do:
-    [
+    [  
         (self image: (Image fromFile: aFileName)) notNil
         ifTrue:
         [
@@ -569,9 +570,22 @@
     ] 
 !
 
-resourceClass: aClassOrSymbol selector: aStringOrSymbol
+loadFromMessage: aMessage
+
+    (self resourceMessage: aMessage) isNil
+    ifTrue:
+    [
+        ^nil
+    ].
 
-    |aClass|
+    ^self loadfromClass: resourceClass andSelector: resourceSelector
+
+   
+!
+
+loadfromClass: aClassOrSymbol andSelector: aStringOrSymbol
+
+    |aClass|       
     imageReaderClass := nil.
     self resourceClass: aClassOrSymbol.
     self resourceSelector: aStringOrSymbol.
@@ -581,6 +595,7 @@
     [ 
         ^self image: (aClass perform: resourceSelector) copy
     ].
+    self warn: 'No class or selector for evaluation detected!!'.
     ^nil
 ! !
 
@@ -604,9 +619,9 @@
 
     |newMag|
     EnterBox new
-        title:'magnification (magX @ magY)';
-        okText:'apply';
-        abortText:'abort';
+        title:'Magnification (magX @ magY)';
+        okText:'Apply';
+        abortText:'Abort';
         action:[:string | newMag := (Object readFromString:string onError:nil)];
         initialText:(magnification printString);
         showAtPointer.
@@ -618,7 +633,7 @@
 
 loadFromClass
 
-    self resourceMessage: (ResourceSelectionBrowser
+    self loadFromMessage: (ResourceSelectionBrowser
         openOnSuperclass: ApplicationModel
         class: self resourceClass
         selector: self resourceSelector
@@ -663,40 +678,19 @@
     self saveImageFileAs
 !
 
-saveAsMethod
-
-    Object errorSignal handle:
-    [:ex|
-        self warn: ex errorString.
-        ^nil                                 
-    ] 
-    do:
-    [   
-        |imageStoreStream cls|  
-        (self resourceSelector trimBlanks size = 0) | (cls := Smalltalk at: self resourceClass) isClass not 
-            ifTrue: [^self error: 'No class and selector for image detected!!'].
-        self image storeOn: (imageStoreStream := WriteStream on: '').
-        ByteCodeCompiler 
-            compile: (self resourceSelector, '\\' withCRs, '    <resource: #image>\' withCRs, '    ^', imageStoreStream contents)
-            forClass: cls class inCategory: 'resources'.
-        modified := false.
-    ]
-!
-
 saveImageFileAs
 
-    |aFileName|
-
-    (aFileName := (FileSelectionBrowser title: 'Saving Image As...' requestFileName: self image fileName fileFilters: FileSelectionBrowser saveImageFileNameFilters)) notNil
-    ifTrue:
-    [
-        self saveImageFileAs: aFileName
-    ].
+    self saveImageFileAs:
+        (FileSelectionBrowser
+            title: 'Saving Image As'
+            requestFileName: self image fileName
+            fileFilters: FileSelectionBrowser saveImageFileNameFilters)
 !
 
 saveImageFileAs: aFileName
 
-    image notNil
+    aFileName isNil ifTrue: [^nil].
+    image notNil & (aFileName readStream nextWord size > 0)
     ifTrue:
     [
         image fileName: aFileName.
@@ -704,22 +698,21 @@
     ]
     ifFalse:
     [
-        self warn: 'No image detected!!'
+        self warn: 'No image or file name for saving detected!!'
     ]
 !
 
 saveImageMaskFileAs
 
-    |aFileName|
-    (aFileName := (FileSelectionBrowser requestFileName: self image fileName fileFilters: FileSelectionBrowser saveImageFileNameFilters)) notNil
-    ifTrue:
-    [
-        self saveImageMaskFileAs: aFileName
-    ].
+    self saveImageMaskFileAs:
+        (FileSelectionBrowser 
+            requestFileName: self image fileName 
+            fileFilters: FileSelectionBrowser saveImageFileNameFilters)
 !
 
 saveImageMaskFileAs: aFileName
 
+    aFileName isNil ifTrue: [^nil].
     (image notNil and: [image mask notNil])
     ifTrue:
     [
@@ -767,6 +760,42 @@
     ]
 
        
+!
+
+saveMethod
+
+    Object errorSignal handle:
+    [:ex|
+        self warn: ex errorString.
+        ^nil                                 
+    ] 
+    do:
+    [   
+        |imageStoreStream cls|  
+        (self resourceSelector trimBlanks size = 0) | (cls := Smalltalk at: self resourceClass) isClass not 
+            ifTrue: [^self error: 'No class and selector for image detected!!'].
+        self image storeOn: (imageStoreStream := WriteStream on: '').
+        ByteCodeCompiler 
+            compile: (self resourceSelector,
+                '\' withCRs, '    "ImageEditor openOnClass:self andSelector:#', self resourceSelector, '"',
+                '\\' withCRs, '    <resource: #image>\' withCRs, '    ^', imageStoreStream contents)
+            forClass: cls class inCategory: 'resources'.
+        modified := false.
+    ]
+!
+
+saveMethodAs
+
+    (self resourceMessage: (ResourceSelectionBrowser
+            openOnSuperclass: ApplicationModel
+            class: self resourceClass
+            selector: self resourceSelector
+            resourceTypes: #(image fileImage))) notNil
+    ifTrue:
+    [
+        ^self saveMethod
+    ].
+    ^nil
 ! !
 
 !ImageEditView methodsFor:'queries'!
@@ -816,10 +845,15 @@
         modified := false
     ].
     ^true
+!
+
+isGridOn
+
+    ^magnification > gridMagnification
 ! !
 
 !ImageEditView class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libwidg2/ImageEditView.st,v 1.51 1997-12-08 20:25:10 tz Exp $'
+    ^ '$Header: /cvs/stx/stx/libwidg2/ImageEditView.st,v 1.52 1997-12-11 12:43:42 tz Exp $'
 ! !
--- a/ImgEditV.st	Mon Dec 08 21:25:10 1997 +0100
+++ b/ImgEditV.st	Thu Dec 11 13:43:42 1997 +0100
@@ -61,19 +61,17 @@
 
 resourceMessage: aMessage
 
-    (aMessage notNil and: [aMessage trimBlanks size > 0])
+    (aMessage isString and: [aMessage trimBlanks size > 0])
     ifTrue:
     [
-        resourceClass := aMessage readStream nextWord asSymbol.
-        resourceSelector := aMessage reversed readStream nextWord reverse asSymbol.
+        resourceClass := (aMessage readStream upTo: Character space) asSymbol.
+        resourceSelector := (aMessage copy reverse readStream upTo: Character space) reverse asSymbol.
     ]
     ifFalse:
     [
         ^nil
     ].
 
-    ^self resourceClass: resourceClass selector: resourceSelector
-
    
 !
 
@@ -87,9 +85,14 @@
     resourceSelector := aStringOrSymbol asSymbol
 !
 
+selectColor: anArrayTwoColors
+
+    selectColors := anArrayTwoColors
+!
+
 selectedColor
 
-   ^(selectColors at: mouseKeyColorMode) ? Color black
+   ^selectColors at: mouseKeyColorMode
 !
 
 selectedColor: aColor
@@ -107,9 +110,9 @@
     dotW := magnification x.
     dotH := magnification y.
 
-    minX := (x // dotW).
+    minX := x // dotW.
     minX >= iw ifTrue:[minX := iw - 1].
-    minY := (y // dotH).
+    minY := y // dotH.
     minY >= ih ifTrue:[minY := ih - 1].
     maxX := (x + w) // dotW + 1.
     maxX > iw ifTrue:[maxX := iw].
@@ -123,10 +126,11 @@
     maskColor := false.
     image colorsFromX:minX y:minY toX:maxX-1 y:maxY-1 do:
     [:xx :yy :color|
-
-        yy ~~ lastY ifTrue:
+        yy ~~ lastY
+        ifTrue:
         [
-            runW ~~ 0 ifTrue:
+            runW ~~ 0
+            ifTrue:
             [
                 |origin|
                 origin := (x0 * dotW + margin)@(lastY * dotH + margin).
@@ -142,9 +146,11 @@
             lastY := yy.
         ]. 
 
-        color ~~ last ifTrue:
+        color ~~ last
+        ifTrue:
         [
-            runW ~~ 0 ifTrue:
+            runW ~~ 0
+            ifTrue:
             [
                 |origin|
                 origin := (x0 * dotW + margin)@(yy * dotH + margin).
@@ -192,12 +198,6 @@
 
     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.
@@ -205,8 +205,8 @@
     "/ right of image ?
     adjust == #center ifTrue:
     [
-        xI := (width - (margin * 2) - ih) // 2.
-        yI := (height - (margin * 2) - iw) // 2.
+        xI := (width - ih) // 2 - margin.
+        yI := (height - iw) // 2 - margin.
     ]
     ifFalse:
     [
@@ -307,10 +307,10 @@
         |filledPoints|
         filledPoints := image floodFillAt: aPoint//magnification withColor: self selectedColor.
         image restored.
-        filledPoints size < 100
+        filledPoints size < 300
         ifTrue:
         [
-            filledPoints do: [:p| Delay waitForMilliseconds:1. self redraw: ((p * magnification extent: magnification) expandedBy: 1@1)]
+            filledPoints do: [:p| Delay waitForMilliseconds:0.7. self redraw: ((p * magnification extent: magnification) expandedBy: 1@1)]
         ]
         ifFalse:
         [
@@ -332,8 +332,9 @@
 
 getRectangleFrom: aPoint emphasis: emphasis
 
-    |currentPoint currentExtent firstPoint lastCurrentPoint p|
+    |currentPoint currentExtent firstPoint lastCurrentPoint gridCorrection p|
     firstPoint := currentPoint := lastCurrentPoint := aPoint//magnification*magnification.
+    self isGridOn ifFalse: [gridCorrection := 0] ifTrue: [gridCorrection := 1].
     [Display anyButtonPressed]
     whileTrue:
     [   
@@ -348,7 +349,7 @@
             emphasis = #inverseFilledBox
             ifTrue:
             [
-                self xoring: [self fillRectangle: ((firstPoint min: currentPoint) + 1 extent: currentExtent - 1)]
+                self xoring: [self fillRectangle: ((firstPoint min: currentPoint) + 1 extent: currentExtent - gridCorrection)]
             ].
             emphasis = #box
             ifTrue:
@@ -357,7 +358,7 @@
                     ifTrue: [self paint: self selectedColor]
                     ifFalse: [self paint: self viewBackground].
                 self lineWidth: magnification x.
-                self displayRectangle: ((firstPoint min: currentPoint) + (magnification x//2) extent: (currentExtent - (magnification x))).
+                self displayRectangle: ((firstPoint min: currentPoint) + (magnification x//2) + 1 extent: (currentExtent - (magnification x)) - gridCorrection + 1).
                 self lineWidth: 1.
             ].
             emphasis = #filledBox
@@ -366,8 +367,7 @@
                 self selectedColor ~= Color noColor
                     ifTrue: [self paint: self selectedColor]
                     ifFalse: [self paint: self viewBackground].
-                self fillRectangle: ((firstPoint min: currentPoint) extent: currentExtent).
-                self displayRectangle: ((firstPoint min: currentPoint) extent: currentExtent).
+                self fillRectangle: ((firstPoint min: currentPoint) + 1 extent: currentExtent - gridCorrection).
             ].
         ]. 
         self drawLabel: currentPoint//magnification.
@@ -381,7 +381,7 @@
 
     Object errorSignal handle:
     [:ex|
-        WarningBox warn: 'Pasting into this image failed!!'.
+        self warn: 'Pasting at selected point failed!!'.
     ] 
     do:
     [   
@@ -443,12 +443,12 @@
     |b newSize|
 
     b := EnterBox new.
-    b title:'resize image'.
-    b okText:'apply'.
-    b abortText:'abort'.
+    b title:'Image new size:'.
+    b okText:'OK'.
+    b abortText:'Cancel'.
     b initialText:image extent printString.
     b showAtPointer.
-    (newSize := Object readFromString: b contents onError:nil) notNil
+    (b accepted and: [(newSize := Object readFromString: b contents onError:nil) notNil])
     ifTrue:
     [
         self image: (image magnifiedBy: newSize/image extent)
@@ -460,16 +460,16 @@
     |b rotation|
 
     b := EnterBox new.
-    b title:'rotate image'.
-    b okText:'apply'.
-    b abortText:'abort'.
+    b title:'Image new rotation:'.
+    b okText:'OK'.
+    b abortText:'Cancel'.
     b initialText: '0'.
     b showAtPointer.
-    (rotation := Object readFromString: b contents onError:nil) notNil
+    (b accepted and: [(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.'.
+            self warn: 'Image rotation failed.\' withCRs, 'An increase of image depth could help.'.
         ] 
         do:
         [   
@@ -499,7 +499,7 @@
 
 drawFrameAt: aPoint
 
-    magnification > gridMagnification
+    self isGridOn
     ifTrue:
     [   
         |lineStartingPoint lineEndingPoint oldColor|
@@ -518,6 +518,7 @@
 !
 
 drawLabel: aLabel
+
     coordInfoBlock notNil
     ifTrue:
     [         
@@ -554,7 +555,7 @@
         ^nil
     ] 
     do:
-    [
+    [  
         (self image: (Image fromFile: aFileName)) notNil
         ifTrue:
         [
@@ -569,9 +570,22 @@
     ] 
 !
 
-resourceClass: aClassOrSymbol selector: aStringOrSymbol
+loadFromMessage: aMessage
+
+    (self resourceMessage: aMessage) isNil
+    ifTrue:
+    [
+        ^nil
+    ].
 
-    |aClass|
+    ^self loadfromClass: resourceClass andSelector: resourceSelector
+
+   
+!
+
+loadfromClass: aClassOrSymbol andSelector: aStringOrSymbol
+
+    |aClass|       
     imageReaderClass := nil.
     self resourceClass: aClassOrSymbol.
     self resourceSelector: aStringOrSymbol.
@@ -581,6 +595,7 @@
     [ 
         ^self image: (aClass perform: resourceSelector) copy
     ].
+    self warn: 'No class or selector for evaluation detected!!'.
     ^nil
 ! !
 
@@ -604,9 +619,9 @@
 
     |newMag|
     EnterBox new
-        title:'magnification (magX @ magY)';
-        okText:'apply';
-        abortText:'abort';
+        title:'Magnification (magX @ magY)';
+        okText:'Apply';
+        abortText:'Abort';
         action:[:string | newMag := (Object readFromString:string onError:nil)];
         initialText:(magnification printString);
         showAtPointer.
@@ -618,7 +633,7 @@
 
 loadFromClass
 
-    self resourceMessage: (ResourceSelectionBrowser
+    self loadFromMessage: (ResourceSelectionBrowser
         openOnSuperclass: ApplicationModel
         class: self resourceClass
         selector: self resourceSelector
@@ -663,40 +678,19 @@
     self saveImageFileAs
 !
 
-saveAsMethod
-
-    Object errorSignal handle:
-    [:ex|
-        self warn: ex errorString.
-        ^nil                                 
-    ] 
-    do:
-    [   
-        |imageStoreStream cls|  
-        (self resourceSelector trimBlanks size = 0) | (cls := Smalltalk at: self resourceClass) isClass not 
-            ifTrue: [^self error: 'No class and selector for image detected!!'].
-        self image storeOn: (imageStoreStream := WriteStream on: '').
-        ByteCodeCompiler 
-            compile: (self resourceSelector, '\\' withCRs, '    <resource: #image>\' withCRs, '    ^', imageStoreStream contents)
-            forClass: cls class inCategory: 'resources'.
-        modified := false.
-    ]
-!
-
 saveImageFileAs
 
-    |aFileName|
-
-    (aFileName := (FileSelectionBrowser title: 'Saving Image As...' requestFileName: self image fileName fileFilters: FileSelectionBrowser saveImageFileNameFilters)) notNil
-    ifTrue:
-    [
-        self saveImageFileAs: aFileName
-    ].
+    self saveImageFileAs:
+        (FileSelectionBrowser
+            title: 'Saving Image As'
+            requestFileName: self image fileName
+            fileFilters: FileSelectionBrowser saveImageFileNameFilters)
 !
 
 saveImageFileAs: aFileName
 
-    image notNil
+    aFileName isNil ifTrue: [^nil].
+    image notNil & (aFileName readStream nextWord size > 0)
     ifTrue:
     [
         image fileName: aFileName.
@@ -704,22 +698,21 @@
     ]
     ifFalse:
     [
-        self warn: 'No image detected!!'
+        self warn: 'No image or file name for saving detected!!'
     ]
 !
 
 saveImageMaskFileAs
 
-    |aFileName|
-    (aFileName := (FileSelectionBrowser requestFileName: self image fileName fileFilters: FileSelectionBrowser saveImageFileNameFilters)) notNil
-    ifTrue:
-    [
-        self saveImageMaskFileAs: aFileName
-    ].
+    self saveImageMaskFileAs:
+        (FileSelectionBrowser 
+            requestFileName: self image fileName 
+            fileFilters: FileSelectionBrowser saveImageFileNameFilters)
 !
 
 saveImageMaskFileAs: aFileName
 
+    aFileName isNil ifTrue: [^nil].
     (image notNil and: [image mask notNil])
     ifTrue:
     [
@@ -767,6 +760,42 @@
     ]
 
        
+!
+
+saveMethod
+
+    Object errorSignal handle:
+    [:ex|
+        self warn: ex errorString.
+        ^nil                                 
+    ] 
+    do:
+    [   
+        |imageStoreStream cls|  
+        (self resourceSelector trimBlanks size = 0) | (cls := Smalltalk at: self resourceClass) isClass not 
+            ifTrue: [^self error: 'No class and selector for image detected!!'].
+        self image storeOn: (imageStoreStream := WriteStream on: '').
+        ByteCodeCompiler 
+            compile: (self resourceSelector,
+                '\' withCRs, '    "ImageEditor openOnClass:self andSelector:#', self resourceSelector, '"',
+                '\\' withCRs, '    <resource: #image>\' withCRs, '    ^', imageStoreStream contents)
+            forClass: cls class inCategory: 'resources'.
+        modified := false.
+    ]
+!
+
+saveMethodAs
+
+    (self resourceMessage: (ResourceSelectionBrowser
+            openOnSuperclass: ApplicationModel
+            class: self resourceClass
+            selector: self resourceSelector
+            resourceTypes: #(image fileImage))) notNil
+    ifTrue:
+    [
+        ^self saveMethod
+    ].
+    ^nil
 ! !
 
 !ImageEditView methodsFor:'queries'!
@@ -816,10 +845,15 @@
         modified := false
     ].
     ^true
+!
+
+isGridOn
+
+    ^magnification > gridMagnification
 ! !
 
 !ImageEditView class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libwidg2/Attic/ImgEditV.st,v 1.51 1997-12-08 20:25:10 tz Exp $'
+    ^ '$Header: /cvs/stx/stx/libwidg2/Attic/ImgEditV.st,v 1.52 1997-12-11 12:43:42 tz Exp $'
 ! !