#UI_ENHANCEMENT by cg
authorClaus Gittinger <cg@exept.de>
Fri, 20 Jan 2017 23:08:38 +0100
changeset 5413 6211fc3b725a
parent 5412 0cf5d087ba0c
child 5414 641d2f0d748c
#UI_ENHANCEMENT by cg class: ImageEditView added: #redrawImageX:y:width:height:unmaskedOnly:processColorsWith: #showCursorAt:andInformation: removed: #drawCursorAt:withLabel: comment/format in: #boxAt: #circleAt: #copyAt: #drawFrame #editMode #fillAt: #filledBoxAt: #redraw: changed: #buttonMotion:x:y: #buttonPress:x:y: #clipBoard #dragRectangleStartingAt:emphasis: #drawCursorAt: #drawFramesIn: #initialize #performSpecialOperationOn:withColor: #redrawImageX:y:width:height:unmaskedOnly: #redrawX:y:width:height: #specialOperationAt:
ImageEditView.st
--- a/ImageEditView.st	Fri Jan 20 23:05:58 2017 +0100
+++ b/ImageEditView.st	Fri Jan 20 23:08:38 2017 +0100
@@ -63,7 +63,7 @@
 
 initialize
     MaxUndos := 10.
-    GridMagnificationLimit := 8 @ 8.
+    GridMagnificationLimit := 6 @ 6.
 
     EditModePoint := #point.
     EditModeBox := #box.
@@ -187,8 +187,13 @@
 !
 
 clipBoard
-    ^ self getClipboardObject.
-"/    ^ Clipboard
+    |clipboardObject|
+    
+    clipboardObject := self getClipboardObject.
+    clipboardObject isImage ifTrue:[
+        ^ clipboardObject
+    ].
+    ^ Clipboard.
 !
 
 drawingColorHolders
@@ -396,6 +401,8 @@
 !ImageEditView methodsFor:'drawing'!
 
 drawFrame
+    "draws a black frame around the image's bounds"
+    
     self paint:self blackColor.
     self lineWidth: (magnification x//3 min: 3).
     self displayRectangle: ((0@0) extent:(image extent * magnification) + margin).
@@ -403,28 +410,28 @@
 !
 
 drawFramesIn: aRectangle
-
-    magnification >= GridMagnificationLimit
-    ifTrue:
-    [   
-        |origin lineStartingPoint lineEndingPoint oldColor|
+    "draws the pixel frame grid"
+
+    |origin lineStartingPoint lineEndingPoint oldColor mX mY|
+
+    magnification >= GridMagnificationLimit ifTrue: [
+        mX := magnification x.
+        mY := magnification y.
+        
         origin := aRectangle origin - 1.
-        lineStartingPoint := origin + (0@magnification y).
+        lineStartingPoint := origin + (0 @ mY).
         lineEndingPoint   := lineStartingPoint + (aRectangle width@0).
+
         oldColor := self paint.
-        self xoring:
-        [
+        self xoring:[
             self displayLineFrom: lineStartingPoint to: lineEndingPoint.
-            lineStartingPoint x to: lineStartingPoint x + aRectangle width - magnification x by: magnification x do:
-            [:x|   
-                self displayLineFrom: x@(origin y) to: x@(origin y + magnification y)
+            lineStartingPoint x to: lineStartingPoint x + aRectangle width - mX by: mX 
+            do:[:x|   
+                self displayLineFrom: x@(origin y) to: x@(origin y + mY)
             ].
         ].
         self paint: oldColor.
     ]
-
-
-
 !
 
 drawPasteRectangleAt: aPoint
@@ -476,7 +483,6 @@
     self 
         invalidate:(aRectangle origin "+ self viewOrigin" extent:aRectangle extent)
         repairNow:true. 
-"/    super redraw:(aRectangle origin + self viewOrigin extent:aRectangle extent).
 
     "Modified: / 15.11.2001 / 16:43:53 / cg"
 !
@@ -490,6 +496,17 @@
 redrawImageX:x y:y width:w height:h unmaskedOnly:unmaskedOnly
     "redraw the magnified (editing) view of the image"
 
+    self 
+        redrawImageX:x y:y width:w height:h 
+        unmaskedOnly:unmaskedOnly processColorsWith:[:colorIn | colorIn].
+
+    "Created: / 18.5.1999 / 20:13:39 / cg"
+    "Modified: / 18.5.1999 / 20:36:20 / cg"
+!
+
+redrawImageX:x y:y width:w height:h unmaskedOnly:unmaskedOnly processColorsWith:aColorBlock
+    "redraw the magnified (editing) view of the image"
+
     |ih iw magX magY minX maxX minY maxY lastColor lastY runW x0 maskColor mask
      sizeOfMaskPoint useNearestColor origin|
 
@@ -518,8 +535,11 @@
     sizeOfMaskPoint := magnification//3.
     image 
         colorsFromX:minX y:minY toX:maxX-1 y:maxY-1 
-        do:[:xx :yy :color|
-
+        do:[:xx :yy :colorIn|
+            |color|
+            
+            color := aColorBlock value:colorIn.
+            
             shown ifFalse:[^ self].
 
             yy ~~ lastY ifTrue:[
@@ -539,7 +559,6 @@
 
             color ~= lastColor ifTrue:[
                 runW ~~ 0 ifTrue:[
-
                     origin := (x0 * magX + margin)@(yy * magY + margin).
                     (unmaskedOnly not or:[maskColor not]) ifTrue:[
                         self fillFramedRectangle: (origin extent: (runW@magY)).
@@ -589,7 +608,7 @@
 
 redrawX:x y:y width:w height:h
 
-    |xI yI devImage imgWidth imgHeight|
+    |xI yI devImage imgWidth imgHeight mX mY magnifiedWidth magnifiedHeight|
 
     image isNil ifTrue:[^self].
 
@@ -604,44 +623,45 @@
             ].
         ].
         image device == device ifTrue:[
-            ^ super redrawX:x y:y width:w height:h
+            super redrawX:x y:y width:w height:h.
+            self drawFrame.
+            ^ self.
         ].
     ].
 
     "/ self clippingRectangle: (x@y extent:w@h).
-
+    "/ draw the image itself
     self redrawImageX:x y:y width:w height:h.
 
     imgWidth := image width.
     imgHeight := image height.
 
     "/ beyond of image ?
-    adjust == #center ifTrue:
-    [
+    adjust == #center ifTrue:[
         xI := (width - imgWidth) // 2 - margin.
         yI := (height - imgHeight) // 2 - margin.
-    ]
-    ifFalse:
-    [
+    ] ifFalse:[
         xI := yI := margin
     ].
 
-    (x + w - 1) > (xI + (magnification x * imgWidth)) ifTrue:
-    [
-        self clearRectangleX:(xI + (magnification x * imgWidth))
-                           y:y
-                       width:(x + w - (magnification x * imgWidth) - xI)
-                      height:h
+    mX := magnification x.
+    mY := magnification y.
+    magnifiedWidth := mX * imgWidth.
+    magnifiedHeight := mY * imgHeight.
+    
+    "/ draw the rest to the right and at the bottom
+    (x + w - 1) > (xI + magnifiedWidth) ifTrue:[
+        self 
+            clearRectangleX:(xI + magnifiedWidth) y:y
+            width:(x + w - magnifiedWidth - xI) height:h
     ].
-    (y + h - 1) > (yI + (magnification y * imgHeight)) ifTrue:
-    [
-        self clearRectangleX:margin
-                           y:(yI + (magnification y * imgHeight))
-                       width:w
-                      height:(y + h - (magnification y * imgHeight) - yI)  
+    (y + h - 1) > (yI + magnifiedHeight) ifTrue:[
+        self 
+            clearRectangleX:margin y:(yI + magnifiedHeight)
+            width:w height:(y + h - magnifiedHeight - yI)  
     ].
     self drawFrame.
-    self clippingRectangle: nil.
+    self clippingBounds: nil.
 
     "Modified: / 31.7.1998 / 02:22:45 / cg"
 !
@@ -695,6 +715,21 @@
 !ImageEditView methodsFor:'edit modes'!
 
 editMode
+    "is one of the edit modes:
+
+        EditModePoint
+        EditModeBox
+        EditModePaste
+        EditModePasteUnder
+        EditModePasteWithMask 
+        EditModeFilledBox
+        EditModeFill 
+        EditModeCopy 
+        EditModeSpecialOperation 
+        EditModeSpray 
+        EditModeCircle 
+        EditModeSmooth 
+    "
 
     ^editMode
 !
@@ -737,7 +772,7 @@
     (x < 0 or:[y < 0]) ifTrue:[
         ^ self
     ].
-    readOnly ifTrue:[^ self].
+    "/ readOnly ifTrue:[^ self].
 
     p := x@y.
 
@@ -763,7 +798,7 @@
         ^ self
     ].
 
-    "/button up (care for paste-mode, dragging the pasted image)
+    "/ button is up (care for paste-mode, dragging the pasted image)
     self drawCursorAt:p.
     self inPasteMode ifTrue: [
         self sensor shiftDown ifTrue:[
@@ -812,7 +847,10 @@
             masked ifTrue:[self selectedColorIndex:nil].
             self changed:#selectedColor with:clr.
         ] ifFalse:[
-            readOnly ifFalse:[
+            (readOnly not 
+              or:[editMode == EditModeCopy
+              or:[editMode == EditModeSpecialOperation]]
+            ) ifTrue:[
                 (button between:1 and:2) ifTrue:[
                     mouseKeyColorMode := button.
                     self makeUndo.
@@ -891,7 +929,8 @@
 !ImageEditView methodsFor:'image editing'!
 
 boxAt: aPoint
-    "draw a rectangular outline with the currently selected color"
+    "drag a rectangular outline, 
+     when released draw a rectangle with the currently selected color"
 
     |choosenBox imageBox clr pix|
 
@@ -923,7 +962,8 @@
 !
 
 circleAt: aPoint
-    "draw an elliptic outline with the currently selected color"
+    "drag an ellipse, 
+     when released draw an ellipse with the currently selected color"
 
     |choosenBox imageBox clr pix|
 
@@ -951,6 +991,9 @@
 !
 
 copyAt: aPoint
+    "drag a filled box, 
+     when released copy the selected rectangle to the clipboard"
+
     |choosenBox box copiedImage|
 
     choosenBox := self dragRectangleStartingAt: aPoint emphasis: #inverseFilledBox.
@@ -1103,7 +1146,8 @@
 !
 
 filledBoxAt: aPoint
-    "fill a rectangular area with the currently selected color"
+    "drag a filled box, 
+     when released fill a rectangular area with the currently selected color"
 
     |choosenBox imageBox clr pix|
 
@@ -1544,38 +1588,52 @@
 !
 
 performSpecialOperationOn:imageBox withColor:clr
-    |operation x0 y0 x1 y1 pixelAction requiredColors missingColors answer hue|
-
+    |listOfOpNames listOfOpSelectors operation x0 y0 x1 y1 pixelAction requiredColors missingColors answer hue|
+
+    listOfOpNames := OrderedCollection new.
+    listOfOpSelectors := OrderedCollection new. 
+    
+    listOfOpNames add:(resources string:'edit separately'). 
+    listOfOpSelectors add:#edit.
+    
+    self readOnly ifFalse:[
+        listOfOpNames addAll:
+            (resources array:#(
+               '-'
+               'flip vertical'
+               'flip horizontal'
+               '-'
+               'slightly brightened'
+               'slightly darkened'
+               'brightened'
+               'darkened'
+               '-'
+               'make grey'
+               'greyed'
+               'grey pattern'
+               'grey pattern (unmasked)'
+               '-'
+               'reversed'
+               '-'
+               'change hue'
+               'colorize'
+             )).
+                 
+        listOfOpSelectors addAll:
+            #(nil
+              flipVertical flipHorizontal nil
+              slightlyBrightened slightlyDarkened brightened darkened nil 
+              makeGrey greyed greyPattern unmaskedGreyPattern nil 
+              reversed nil 
+              changeHue colorize
+            ).
+    ].
+    
     operation := Dialog 
            choose:(resources string:'Which Operation:')
-           fromList:(resources array:#(
-                       'edit separately'
-                       '-'
-                       'flip vertical'
-                       'flip horizontal'
-                       '-'
-                       'slightly brightened'
-                       'slightly darkened'
-                       'brightened'
-                       'darkened'
-                       '-'
-                       'make grey'
-                       'greyed'
-                       'grey pattern'
-                       'grey pattern (unmasked)'
-                       '-'
-                       'reversed'
-                       '-'
-                       'change hue'
-                       'colorize'
-                     )) 
-           values:#(edit nil
-                    flipVertical flipHorizontal nil
-                    slightlyBrightened slightlyDarkened brightened darkened nil 
-                    makeGrey greyed greyPattern unmaskedGreyPattern nil 
-                    reversed nil 
-                    changeHue colorize) 
-           lines:6
+           fromList:listOfOpNames
+           values:listOfOpSelectors
+           lines:10
            cancel:nil.
 
     self invalidate.
@@ -1902,7 +1960,7 @@
 
     |choosenBox imageBox|
 
-    choosenBox := self dragRectangleStartingAt: aPoint emphasis: #filledBox.
+    choosenBox := self dragRectangleStartingAt: aPoint emphasis:#inverseFilledBox.
     choosenBox isNil ifTrue:[ ^ self ].
 
     imageBox := choosenBox origin//magnification extent: (choosenBox extent//magnification).
@@ -2148,22 +2206,32 @@
 !ImageEditView methodsFor:'image-dragging & info'!
 
 dragRectangleStartingAt:aPointIn emphasis:emphasis
-    "drag a rectangle (filled or unfilled)"
+    "draw a drag rectangle (filled or unfilled, depending on the emphasis arg).
+     This is called by operation like 
+     rectangle, filledRectangle, copy etc. 
+     (i.e. any operation which operates on a box).
+     emphasis is one of:
+        box              - a frame is drawn
+        inverseFilledBox - the dragged box is filled by the inverse color
+        filledBox        - the dragged box is filled with black
+        grayedBox        - the dragged box is drawn with a gray shadow
+    "
 
     |currentPoint currentExtent firstPoint lastCurrentPoint gridCorrection 
-     mp lastMp p whichQuarter scrollX scrollY aPoint|
+     mp lastMp p whichQuarter scrollX scrollY aPoint sensor|
 
     aPoint := aPointIn.
     firstPoint := currentPoint := lastCurrentPoint :=  aPoint//magnification*magnification.
     magnification >= GridMagnificationLimit ifFalse: [gridCorrection := 0] ifTrue: [gridCorrection := 1].
 
-    [self sensor anyButtonPressed] whileTrue: [                                                  
-        (self sensor hasKeyEventFor:nil) ifTrue:[
+    sensor := self sensor.
+    [sensor anyButtonPressed] whileTrue: [                                                  
+        (sensor hasKeyEventFor:nil) ifTrue:[
             self invalidate.
             ^ nil.
         ].
 
-        mp := self sensor mousePoint.
+        mp := sensor mousePoint.
         mp = lastMp ifTrue:[
             Delay waitForSeconds:0.05
         ] ifFalse:[
@@ -2201,22 +2269,48 @@
                  ifTrue:  [(firstPoint y - currentPoint y) > 0 ifTrue: ["4"1@1] ifFalse: ["3"1@0]]
                  ifFalse: [(firstPoint y - currentPoint y) > 0 ifTrue: ["1"0@1] ifFalse: ["2"0@0]].
 
-            self drawCursorAt: p withLabel: 
+            self showCursorAt: p andInformation: 
                 ((firstPoint//magnification - whichQuarter + 1) printString, 
                 ' to: ', 
                 (currentPoint//magnification + whichQuarter) printString),
                 ' (extent: ',
                 (currentExtent//magnification) printString, ')'.
 
-            currentPoint ~= lastCurrentPoint ifTrue:[   
-                emphasis = #inverseFilledBox ifTrue: [
+            currentPoint ~= lastCurrentPoint ifTrue:[
+
+                emphasis == #grayedBox ifTrue:[
+                    "/ does not yet work                
+                    |org ext|
+
+                    "/ org := (firstPoint min: lastCurrentPoint) - 1.
+                    "/ ext := (firstPoint - lastCurrentPoint) abs + 2.
+
+                    (lastCurrentPoint x > currentPoint x
+                      or:[ (lastCurrentPoint y > currentPoint y) ]
+                    ) ifTrue:[
+                        self 
+                            redrawImageX:firstPoint x"-1" y:firstPoint y"-1" 
+                            width:(lastCurrentPoint x-firstPoint x"+2") height:(lastCurrentPoint y-firstPoint y"+2")
+                            unmaskedOnly:false processColorsWith:[:clr | clr ].
+                        "/ self drawFramesIn:(firstPoint corner:lastCurrentPoint).   
+                    ].
+                    
+                    self 
+                        redrawImageX:firstPoint x"-1" y:firstPoint y"-1 "
+                        width:(currentPoint x-firstPoint x"+2") height:(currentPoint y-firstPoint y"+2") 
+                        unmaskedOnly:true processColorsWith:[:clr | Color gray: clr grayIntensity / 2 ].
+                ].
+                
+                emphasis == #inverseFilledBox ifTrue: [
                     self redraw: ((firstPoint min: lastCurrentPoint) - 1 extent: (firstPoint - lastCurrentPoint) abs + 2).
                     self xoring: [ 
                         self fillRectangle: ((firstPoint min: currentPoint) + margin extent: currentExtent - gridCorrection) 
                     ]
                 ].
-                emphasis = #box ifTrue:[
+                
+                emphasis == #box ifTrue:[
                     |origin extent lineWidthY lineWidthX|
+
                     origin := (firstPoint min: lastCurrentPoint) - 1.
                     extent := (firstPoint - lastCurrentPoint) abs + 2.
                     lineWidthY := extent y min: (magnification y + 2).
@@ -2225,24 +2319,24 @@
                     self redraw: ((origin x@(origin y + extent y - lineWidthY)) extent: (extent x@lineWidthY)).
                     self redraw: ((origin x@(origin y + lineWidthY)) extent: (lineWidthX@(0 max: (extent y - (lineWidthY * 2))))).
                     self redraw: (((origin x + extent x - lineWidthX)@(origin y + lineWidthY)) extent: (lineWidthX@(extent y - (lineWidthY * 2)))).
-                    self selectedColor ~= Color noColor
+                    (self selectedColor ~= Color noColor)
                         ifTrue: [self paint: self selectedColor]
                         ifFalse: [self paint: self viewBackground]. 
                     origin := (firstPoint min: currentPoint) + margin.
                     extent := currentExtent - gridCorrection.
                     lineWidthY := extent y min: magnification y.
                     lineWidthX := extent x min: magnification x.
-                    (lineWidthY > 0 and: [lineWidthX > 0])
-                    ifTrue:[
+                    (lineWidthY > 0 and: [lineWidthX > 0]) ifTrue:[
                         self fillRectangle: (origin extent: (extent x@lineWidthY)).
                         self fillRectangle: ((origin x@(origin y + extent y - lineWidthY)) extent: (extent x@lineWidthY)).
                         self fillRectangle: ((origin x@(origin y + lineWidthY)) extent: (lineWidthX@(0 max: (extent y - (lineWidthY * 2))))).
                         self fillRectangle: (((origin x + extent x - lineWidthX)@(origin y + lineWidthY)) extent: (lineWidthX@(extent y - (lineWidthY * 2)))).
                     ]
                 ].
-                emphasis = #filledBox ifTrue:[
+                
+                emphasis == #filledBox ifTrue:[
                     self redraw: ((firstPoint min: lastCurrentPoint) - 1 extent: (firstPoint - lastCurrentPoint) abs + 2).
-                    self selectedColor ~= Color noColor
+                    (self selectedColor ~= Color noColor)
                         ifTrue: [self paint: self selectedColor]
                         ifFalse: [self paint: self viewBackground].
                     self fillRectangle: ((firstPoint min: currentPoint) + margin extent: currentExtent - gridCorrection).
@@ -2259,7 +2353,7 @@
 !
 
 drawCursorAt:aPoint
-    |imgPoint|
+    |imgPoint shownCursor|
 
     readOnly ifTrue:[^ self].
     image isNil ifTrue: [
@@ -2270,25 +2364,29 @@
 
     imgPoint := aPoint // magnification.
     ((imgPoint x between:0 and:(image width-1)) 
-    and:[imgPoint y between:0 and: (image height-1)])
-    ifFalse:[
-        self updateImageInfo: self imageInfoString. 
-        self cursor:Cursor stop.
+      and:[imgPoint y between:0 and: (image height-1)]
+    ) ifFalse:[
+        self updateImageInfo:self imageInfoString. 
+        shownCursor := Cursor stop.
     ] ifTrue: [
         self updateImageInfoFor:imgPoint.
-        self cursor:Cursor crossHair
+        shownCursor := Cursor crossHair
     ].
+    self cursor:shownCursor.
 
     "Modified: / 03-05-2011 / 12:27:52 / cg"
 !
 
-drawCursorAt: aPoint withLabel: aLabel
+showCursorAt: aPoint andInformation: aLabel
+    |shownCursor|
+    
     readOnly ifTrue:[^ self].
 
     ((0@0 extent: image extent * magnification) containsPoint: aPoint)
-         ifTrue: [self cursor:Cursor crossHair]
-         ifFalse:[self cursor:Cursor stop].
-     self updateImageInfo: aLabel.
+         ifTrue: [ shownCursor := Cursor crossHair ]
+         ifFalse:[ shownCursor :=Cursor stop ].
+    self cursor:shownCursor. 
+    self updateImageInfo: aLabel.
 
     "Modified: / 03-05-2011 / 12:28:15 / cg"
 !