ImgEditV.st
author claus
Mon, 03 Jul 1995 04:35:33 +0200
changeset 64 10910b8b003a
parent 61 bf2e9153bc5a
child 71 9f9243f5813b
permissions -rw-r--r--
.

"
 COPYRIGHT (c) 1993 by Claus Gittinger
	      All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"

ImageView subclass:#ImageEditView
	 instanceVariableNames:'magnification colors magnifiedImage
				colorPanel'
	 classVariableNames:''
	 poolDictionaries:''
	 category:'Views-Misc'
!

ImageEditView comment:'
COPYRIGHT (c) 1993 by Claus Gittinger
	      All Rights Reserved

a View to edit images - in construction

$Header: /cvs/stx/stx/libwidg2/Attic/ImgEditV.st,v 1.13 1995-07-03 02:35:15 claus Exp $
'!

!ImageEditView class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1993 by Claus Gittinger
	      All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"
!

documentation
"
    This View will eventually be able to edit bitmap images.
    For now, it is not.
"
! !

!ImageEditView methodsFor:'queries'!

widthOfContents
    "return the images width"

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

heightOfContents
    "return the images height"

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

!ImageEditView methodsFor:'accessing'!

image:anImage
    magnification := 1@1.
    magnifiedImage := nil.
    super image:anImage
! !

!ImageEditView methodsFor:'menu actions'!

saveAs
    "save contents into a file 
     - ask user for filename using a fileSelectionBox."

    |fileName|

    fileName := Dialog
		    requestFileName:'save image in:'
		    default:''
		    ok:'save'
		    abort:'abort'
		    pattern:'*.tiff'.

    fileName notNil ifTrue:[
	image saveOn:fileName
    ].
!

showColors
    colorPanel isNil ifTrue:[
	colorPanel := ColorPanel new
    ].
    colorPanel shown ifFalse:[
	colorPanel realize
    ]
!

changeMagnification
    |b|

    b := EnterBox new.
    b title:'magnification (magX @ magY)'.
    b okText:'apply'.
    b abortText:'abort'.
    b action:[:string | self magnification:(Object readFromString:string)].
    b initialText:(magnification printString).
    b showAtPointer
!

magnification:aMagnificationPoint
    |nPixel savedImage|

    magnification ~= aMagnificationPoint ifTrue:[
	"show wait cursor; although magnification is fast, dithering may take a while"
	self cursor:Cursor wait.

	(device visualType == #PseudoColor) ifTrue:[
	    "keep colors - otherwise they might get collected & changed"
	    colors := IdentitySet new.
	].

	magnification := aMagnificationPoint asPoint.

	"use a magnified image, if its size wont be too big"
	magnifiedImage := nil.

	"avoid slow scroll"
	savedImage := image.
	image := nil.
	self scrollToTopLeft.
	image := savedImage.

	magnification ~= (1@1) ifTrue:[
	    nPixel := image width * image height * magnification x * magnification y.
	    nPixel <= (device width * device height) ifTrue:[
		Transcript showCr:'magnifying ..'; endEntry.
		magnifiedImage := image magnifyBy:magnification
	    ].
	].

	self contentsChanged.
	self redraw.
	self cursor:Cursor normal
    ]
! !

!ImageEditView methodsFor:'drawing'!

redraw
    |x0 y h w dotW dotH color last runW|

    image isNil ifTrue:[^ self].

    magnification = (1@1) ifTrue:[
	^ super redraw
    ].
    magnifiedImage notNil ifTrue:[
	magnifiedImage := magnifiedImage on:device.
	self clear.
	self foreground:Black background:White.
	self function:#copy.
	self displayOpaqueForm:magnifiedImage x:0 y:0.
	^ self
    ].

    self clear.

    h := image height.
    w := image width.
    dotW := magnification x.
    dotH := magnification y.
    ((h * dotH > height) or:[w * dotW > width]) ifTrue:[
	^ self redrawX:0 y:0 width:width height:height
    ].

    y := 0.
    0 to:h-1 do:[:row |
	runW := 0.
	x0 := 0.
	image atY:row from:0 to:(w-1) do:[:x :color |
	    color ~= last ifTrue:[
		runW ~~ 0 ifTrue:[
		    self fillRectangleX:x0 y:y width:runW height:dotH.
		].
		colors notNil ifTrue:[colors add:color].
		self paint:color.
		last := color.
		x0 := x.
		runW := 0.
	    ].
	    runW := runW + dotW
	].
	self fillRectangleX:x0 y:y width:runW height:dotH.
	y := y + dotH
    ]
!

redrawX:x y:y width:w height:h
    |area dx dy ih iw dotW dotH minX maxX minY maxY color last runW x0|

    image isNil ifTrue:[^ self].

    area := Rectangle left:x top:y width:w height:h.      
    self clippedTo:area do:[
	magnification = (1@1) ifTrue:[
	    self redraw
	] ifFalse:[
	    magnifiedImage notNil ifTrue:[
		self redraw
	    ] ifFalse:[
		self clear.
		ih := image height.
		iw := image width.
		dotW := magnification x.
		dotH := magnification y.

		minX := x // dotW.
		minY := y // dotW.
		maxX := (x + w) // dotW + 1.
		maxX > iw ifTrue:[
		    maxX := iw
		].
		maxY := (y + h) // dotH + 1.
		maxY > ih ifTrue:[
		    maxY := ih
		].

		dy := minY * dotH.
		minY to:maxY-1 do:[:row |
		    dx := minX * dotW.
		    x0 := dx.
		    runW := 0.
		    image atY:row from:minX to:(maxX-1) do:[:x :color |
			runW ~~ 0 ifTrue:[
			    self fillRectangleX:x0 y:dy width:runW height:dotH.
			].
			color ~= last ifTrue:[
			    colors notNil ifTrue:[colors add:color].
			    self paint:color.
			    last := color.
			    runW := 0.
			    x0 := x * dotW.
			].
			runW := runW + dotW
		    ].
		    self fillRectangleX:x0 y:dy width:runW height:dotH.
		    dy := dy + dotH
		]
	    ]
	]
    ]
! !

!ImageEditView methodsFor:'initialization'!

initializeMiddleButtonMenu
    |m|

    m := (PopUpMenu
	       labels:(resources array:
			  #('save as ...'
			    '-'
			    'magnification'
"/                            'colors'
			    'effects'
			   ))
	    selectors:#(saveAs
			nil
			changeMagnification
"/                        showColors
			effects
		       )
	     receiver:self
		  for:self).
    self middleButtonMenu:m.

    m subMenuAt:#effects put:(
	PopUpMenu labels:(resources array:#(
			    'flip - vertical'
			    'flip - horizontal'
"
			    '-'
			    'blurr'
"
			   ))
	       selectors:#(
			    flipVertical
			    flipHorizontal
"
			    nil
			    blurr
"
			   )
		receiver:self
		     for:self

    ).

    "
     ImageEditView openOn:'bitmaps/SBrowser.xbm'
     ImageEditView openOn:'bitmaps/garfield.gif'
    "
!

initialize
    super initialize.
    magnification := 1@1.
    colors := nil
! !

!ImageEditView methodsFor:'event handling'!

showColorAtX:x y:y
    |pi clr|

    pi := (x @ y) - margin.
    pi := pi // magnification.
    ((0@0 corner:image extent) containsPoint:pi) ifTrue:[
	clr := image at:pi.
	colorPanel notNil ifTrue:[
	    colorPanel setColor:clr.
	] ifFalse:[
	    Transcript showCr:clr displayString
	]
    ]
!

buttonMotion:state x:x y:y
    self showColorAtX:x y:y.
!

buttonPress:button x:x y:y
    button == 1 ifTrue:[
	self showColorAtX:x y:y.
	^ self
    ].
    super buttonPress:button x:x y:y
! !

!ImageEditView methodsFor:'image processing'!

performImageOperation:operation withArguments:args
    |oldMag|

    windowGroup withCursor:Cursor wait do:[
	oldMag := magnification.
	magnifiedImage := nil.
	magnification := 1@1.
	image perform:operation withArguments:args.
	(oldMag isNil or:[oldMag = magnification]) ifTrue:[
	    self redraw
	] ifFalse:[
	    self magnification:oldMag.
	]
    ]
!

flipVertical
    self performImageOperation:#flipVertical withArguments:nil
!

flipHorizontal
    self performImageOperation:#flipHorizontal withArguments:nil
!

blurr
    self performImageOperation:#blurr withArguments:nil
! !

!ImageEditView methodsFor:'release'!

destroy
    colors := nil.
    magnifiedImage := nil.
    colorPanel notNil ifTrue:[
	colorPanel destroy.
	colorPanel := nil.
    ].
    super destroy.
! !