ImgEditV.st
changeset 386 71766a2845ab
equal deleted inserted replaced
385:059ced1c8344 386:71766a2845ab
       
     1 "
       
     2  COPYRIGHT (c) 1993 by Claus Gittinger
       
     3 	      All Rights Reserved
       
     4 
       
     5  This software is furnished under a license and may be used
       
     6  only in accordance with the terms of that license and with the
       
     7  inclusion of the above copyright notice.   This software may not
       
     8  be provided or otherwise made available to, or used by, any
       
     9  other person.  No title to or ownership of the software is
       
    10  hereby transferred.
       
    11 "
       
    12 
       
    13 ImageView subclass:#ImageEditView
       
    14 	instanceVariableNames:'magnification gridMagnification selectColors imageReaderClass
       
    15 		resourceClass resourceSelector editMode mouseKeyColorMode
       
    16 		undoImage modified coordInfoBlock'
       
    17 	classVariableNames:'Clipboard'
       
    18 	poolDictionaries:''
       
    19 	category:'Views-Misc'
       
    20 !
       
    21 
       
    22 !ImageEditView class methodsFor:'documentation'!
       
    23 
       
    24 copyright
       
    25 "
       
    26  COPYRIGHT (c) 1993 by Claus Gittinger
       
    27 	      All Rights Reserved
       
    28 
       
    29  This software is furnished under a license and may be used
       
    30  only in accordance with the terms of that license and with the
       
    31  inclusion of the above copyright notice.   This software may not
       
    32  be provided or otherwise made available to, or used by, any
       
    33  other person.  No title to or ownership of the software is
       
    34  hereby transferred.
       
    35 "
       
    36 !
       
    37 
       
    38 documentation
       
    39 "
       
    40     This View will eventually be able to edit bitmap images.
       
    41     For now, it is not.
       
    42 
       
    43     [author:]
       
    44         Claus Gittinger
       
    45 
       
    46     [see also:]
       
    47         Image Form
       
    48 
       
    49     [start with:]
       
    50         ImageEditView openOn:'bitmaps/gifImages/garfield.gif'
       
    51         ImageEditView openOnImage:(Image fromFile:'bitmaps/gifImages/garfield.gif')
       
    52 "
       
    53 ! !
       
    54 
       
    55 !ImageEditView methodsFor:'accessing'!
       
    56 
       
    57 coordInfoBlock: aBlock
       
    58 
       
    59     coordInfoBlock := aBlock
       
    60 !
       
    61 
       
    62 gridMagnification: aPoint
       
    63 
       
    64     gridMagnification := aPoint
       
    65 !
       
    66 
       
    67 imageReaderClass
       
    68 
       
    69     ^imageReaderClass
       
    70 !
       
    71 
       
    72 magnification
       
    73 
       
    74     ^magnification
       
    75 
       
    76 !
       
    77 
       
    78 magnification:aPoint
       
    79 
       
    80     magnification ~= aPoint
       
    81     ifTrue:
       
    82     [
       
    83         magnification := aPoint asPoint.
       
    84         self scrollToTopLeft.
       
    85         self contentsChanged.
       
    86         self invalidate.
       
    87     ].
       
    88 !
       
    89 
       
    90 resourceClass
       
    91 
       
    92     ^resourceClass
       
    93 !
       
    94 
       
    95 resourceClass: aClassOrSymbol
       
    96 
       
    97     resourceClass := aClassOrSymbol isClass ifTrue: [aClassOrSymbol name] ifFalse: [aClassOrSymbol asSymbol].
       
    98 
       
    99 !
       
   100 
       
   101 resourceMessage
       
   102 
       
   103     ^resourceClass, ' ', resourceSelector
       
   104 !
       
   105 
       
   106 resourceMessage: aMessage
       
   107 
       
   108     (aMessage notNil and: [aMessage trimBlanks size > 0])
       
   109     ifTrue:
       
   110     [
       
   111         resourceClass := aMessage readStream nextWord asSymbol.
       
   112         resourceSelector := aMessage reversed readStream nextWord reverse asSymbol.
       
   113     ]
       
   114     ifFalse:
       
   115     [
       
   116         ^nil
       
   117     ].
       
   118 
       
   119     ^self resourceClass: resourceClass selector: resourceSelector
       
   120 
       
   121    
       
   122 !
       
   123 
       
   124 resourceSelector
       
   125 
       
   126     ^resourceSelector
       
   127 !
       
   128 
       
   129 resourceSelector: aStringOrSymbol
       
   130 
       
   131     resourceSelector := aStringOrSymbol asSymbol
       
   132 !
       
   133 
       
   134 selectedColor
       
   135 
       
   136    ^selectColors at: mouseKeyColorMode
       
   137 !
       
   138 
       
   139 selectedColor: aColor
       
   140 
       
   141     selectColors at: mouseKeyColorMode put: aColor
       
   142 ! !
       
   143 
       
   144 !ImageEditView methodsFor:'drawing'!
       
   145 
       
   146 redrawImageX:x y:y width:w height:h
       
   147     |ih iw dotW dotH minX maxX minY maxY color last lastY runW x0 xI yI maskColor|
       
   148 
       
   149     ih := image height.
       
   150     iw := image width.
       
   151     dotW := magnification x.
       
   152     dotH := magnification y.
       
   153 
       
   154     minX := (x // dotW).
       
   155     minX >= iw ifTrue:[minX := iw - 1].
       
   156     minY := (y // dotH).
       
   157     minY >= ih ifTrue:[minY := ih - 1].
       
   158     maxX := (x + w) // dotW + 1.
       
   159     maxX > iw ifTrue:[maxX := iw].
       
   160     maxY := (y + h) // dotH + 1.
       
   161     maxY > ih ifTrue:[maxY := ih].
       
   162 
       
   163     lastY := -1.
       
   164 
       
   165     x0 := minX.
       
   166     runW := 0.
       
   167     maskColor := false.
       
   168     image colorsFromX:minX y:minY toX:maxX-1 y:maxY-1 do:
       
   169     [:xx :yy :color|
       
   170 
       
   171         yy ~~ lastY ifTrue:
       
   172         [
       
   173             runW ~~ 0 ifTrue:
       
   174             [
       
   175                 |origin|
       
   176                 origin := (x0 * dotW + margin)@(lastY * dotH + margin).
       
   177                 self fillRectangle: (origin extent: (runW@dotH)).                    
       
   178                 0 to: runW by: dotW do: [:xxx| self drawFrameAt: ((origin x + xxx) @origin y)].
       
   179                 maskColor ifTrue:
       
   180                 [
       
   181                     self drawMaskPointAt: origin
       
   182                 ].
       
   183                 runW := 0.
       
   184             ]. 
       
   185             x0 := xx.
       
   186             lastY := yy.
       
   187         ]. 
       
   188 
       
   189         color ~~ last ifTrue:
       
   190         [
       
   191             runW ~~ 0 ifTrue:
       
   192             [
       
   193                 |origin|
       
   194                 origin := (x0 * dotW + margin)@(yy * dotH + margin).
       
   195                 self fillRectangle: (origin extent: (runW@dotH)).
       
   196                 0 to: runW by: dotW do: [:xxx| self drawFrameAt: ((origin x + xxx) @origin y)].
       
   197                 maskColor ifTrue:
       
   198                 [
       
   199                     self drawMaskPointAt: origin
       
   200                 ].
       
   201                 runW := 0.
       
   202             ].
       
   203 
       
   204             self paint: (last := color).
       
   205             image mask notNil ifTrue:
       
   206             [  
       
   207                 maskColor := false.
       
   208                 (image mask colorAt: xx@yy) = Color black ifTrue:
       
   209                 [
       
   210                     self paint: (last := self viewBackground).
       
   211                     maskColor := true.
       
   212                 ].
       
   213                 last := nil.
       
   214             ].
       
   215             runW := 0.
       
   216             x0 := xx.
       
   217         ].  
       
   218         runW := runW + dotW
       
   219     ].
       
   220     runW ~~ 0 ifTrue:
       
   221     [
       
   222         |origin|
       
   223         origin := (x0 * dotW + margin)@(lastY * dotH + margin).
       
   224         self fillRectangle: (origin extent: runW@dotH).
       
   225         0 to: runW by: dotW do: [:xxx| self drawFrameAt: ((origin x + xxx) @origin y)].
       
   226         maskColor ifTrue:
       
   227         [
       
   228             self drawMaskPointAt: origin.
       
   229         ].
       
   230         runW := 0.
       
   231     ].
       
   232 !
       
   233 
       
   234 redrawX:x y:y width:w height:h
       
   235     |ih iw xI yI|
       
   236 
       
   237     image isNil ifTrue:[^self].
       
   238 
       
   239     magnification = (1@1) ifTrue:
       
   240     [
       
   241         super redrawX:x y:y width:w height:h.
       
   242         self drawFrame.
       
   243         ^ self
       
   244     ].
       
   245     self clippingRectangle: (x@y extent: w@h). 
       
   246 
       
   247     self redrawImageX:x y:y width:w height:h.
       
   248 
       
   249     "/ right of image ?
       
   250     adjust == #center ifTrue:
       
   251     [
       
   252         xI := (width - (margin * 2) - ih) // 2.
       
   253         yI := (height - (margin * 2) - iw) // 2.
       
   254     ]
       
   255     ifFalse:
       
   256     [
       
   257         xI := yI := margin
       
   258     ].
       
   259     (x + w - 1) > (xI + (magnification x * image width)) ifTrue:
       
   260     [
       
   261         self clearRectangleX:(xI + (magnification x * image width))
       
   262                            y:y
       
   263                        width:(x + w - (magnification x * image width) - xI)
       
   264                       height:h
       
   265     ].
       
   266     (y + h - 1) > (yI + (magnification y * image height)) ifTrue:
       
   267     [
       
   268         self clearRectangleX:margin
       
   269                            y:(yI + (magnification y * image height))
       
   270                        width:w
       
   271                       height:(y + h - (magnification y * image height) - yI)  
       
   272     ].
       
   273     self drawFrame.
       
   274     self clippingRectangle: nil.
       
   275 ! !
       
   276 
       
   277 !ImageEditView methodsFor:'edit modes'!
       
   278 
       
   279 editMode
       
   280 
       
   281     editMode isNil ifTrue: [editMode := 'point'].
       
   282     ^editMode
       
   283 !
       
   284 
       
   285 editMode:aMode
       
   286 
       
   287     editMode := aMode
       
   288 !
       
   289 
       
   290 mouseKeyColorMode
       
   291 
       
   292     ^mouseKeyColorMode printString
       
   293 !
       
   294 
       
   295 mouseKeyColorMode:aMode
       
   296 
       
   297     mouseKeyColorMode := aMode asInteger
       
   298 ! !
       
   299 
       
   300 !ImageEditView methodsFor:'event handling'!
       
   301 
       
   302 buttonMotion:state x:x y:y
       
   303 
       
   304     self selectedColor notNil & image notNil & (self imageContainsPoint: x@y) & (editMode = 'point')
       
   305         ifTrue: [^self pointAt: x@y].
       
   306 !
       
   307 
       
   308 buttonPress:button x:x y:y
       
   309 
       
   310     self selectedColor notNil & image notNil & (self imageContainsPoint: x@y)
       
   311     ifTrue:
       
   312     [   
       
   313         undoImage := image copy.
       
   314         mouseKeyColorMode := button.
       
   315         (editMode = 'point')   ifTrue: [self pointAt: x@y].
       
   316         (editMode = 'replace') ifTrue: [self replaceAt: x@y].
       
   317         (editMode = 'paste')   ifTrue: [self pasteAt: x@y].
       
   318         (editMode = 'box') | (editMode = 'copy') ifTrue: [self boxAt: x@y].
       
   319         ^self
       
   320     ].
       
   321 ! !
       
   322 
       
   323 !ImageEditView methodsFor:'image drawing'!
       
   324 
       
   325 boxAt: aPoint
       
   326 
       
   327     |firstPoint currentPoint lastCurrentPoint currentExtent imageFirstPoint imageExtent|
       
   328 
       
   329     firstPoint := lastCurrentPoint := aPoint//magnification*magnification.
       
   330     [Display anyButtonPressed]
       
   331     whileTrue:
       
   332     [   
       
   333         currentPoint := (0@0) max: (image extent * magnification min: (self translation negated + (device translatePoint: self sensor mousePoint from:device rootView id to:self id))).
       
   334         currentPoint := currentPoint//magnification*magnification.
       
   335         currentExtent := (firstPoint - currentPoint) abs.
       
   336         currentPoint ~= lastCurrentPoint ifTrue:
       
   337         [
       
   338             self redraw: ((firstPoint min: lastCurrentPoint) - 1 extent: (firstPoint - lastCurrentPoint) abs + 2).
       
   339             editMode = 'copy'
       
   340             ifTrue:
       
   341             [
       
   342                 self xoring: [self fillRectangle: ((firstPoint min: currentPoint) + 1 extent: currentExtent - 1)]
       
   343             ].
       
   344             editMode = 'box'
       
   345             ifTrue:
       
   346             [
       
   347                 self selectedColor ~= Color noColor
       
   348                     ifTrue: [self paint: self selectedColor]
       
   349                     ifFalse: [self paint: self viewBackground].
       
   350                 self fillRectangle: ((firstPoint min: currentPoint) + 1 extent: currentExtent - 1)
       
   351             ]. 
       
   352         ]. 
       
   353         self drawLabel: currentPoint//magnification.
       
   354         lastCurrentPoint := currentPoint.
       
   355     ].
       
   356 
       
   357     imageFirstPoint := (firstPoint min: currentPoint)//magnification.
       
   358     imageExtent := currentExtent//magnification.
       
   359     editMode = 'box'
       
   360     ifTrue:
       
   361     [
       
   362         self selectedColor ~= Color noColor
       
   363         ifTrue:
       
   364         [   
       
   365             image mask notNil ifTrue: [image mask fillRectangleX: imageFirstPoint x y: imageFirstPoint y width: imageExtent x height: imageExtent y with:Color white].
       
   366             image fillRectangleX: imageFirstPoint x y: imageFirstPoint y width: imageExtent x height: imageExtent y with: self selectedColor.
       
   367             self paint: self selectedColor.
       
   368         ] 
       
   369         ifFalse:
       
   370         [
       
   371             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]).
       
   372             image mask notNil ifTrue: [image mask fillRectangleX: imageFirstPoint x y: imageFirstPoint y width: imageExtent x height: imageExtent y with: Color black].
       
   373             self paint: self viewBackground.
       
   374         ].
       
   375         image restored.
       
   376         modified := true.
       
   377     ].
       
   378     editMode = 'copy'
       
   379     ifTrue:
       
   380     [      
       
   381         Clipboard := image subImageIn: (imageFirstPoint extent: imageExtent)
       
   382     ].
       
   383     self redraw: ((firstPoint min: currentPoint) - 1 extent: (firstPoint - currentPoint) abs + 2).    
       
   384 !
       
   385 
       
   386 pasteAt: aPoint
       
   387 
       
   388     Object errorSignal handle:
       
   389     [:ex|
       
   390         WarningBox warn: 'Pasting into this image failed!!'.
       
   391     ] 
       
   392     do:
       
   393     [   
       
   394         |imagePoint|
       
   395         imagePoint := aPoint//magnification.
       
   396         image copyFrom: Clipboard x:0 y:0 toX: imagePoint x y: imagePoint y width: Clipboard width height: Clipboard height.
       
   397         self redraw: (imagePoint * magnification extent: (Clipboard extent * magnification)).
       
   398         self drawLabel: imagePoint.
       
   399         image restored.
       
   400         modified := true.
       
   401     ]
       
   402 !
       
   403 
       
   404 pointAt: aPoint
       
   405 
       
   406     |imagePoint|
       
   407     imagePoint := aPoint//magnification.
       
   408     self selectedColor ~= Color noColor
       
   409     ifTrue:
       
   410     [   
       
   411         image mask notNil ifTrue: [image mask colorAt: imagePoint put: Color white].
       
   412         image colorAt: imagePoint put: self selectedColor.
       
   413         self paint: self selectedColor.
       
   414     ] 
       
   415     ifFalse:
       
   416     [
       
   417         image colorAt: imagePoint put: ((image colorMap includes: Color black) ifTrue: [Color black] ifFalse: [image colorMap first]).
       
   418         image mask notNil ifTrue: [image mask colorAt: imagePoint put: Color black].
       
   419         self paint:self viewBackground.
       
   420     ].
       
   421 
       
   422     self fillRectangle: (imagePoint * magnification + 1 extent: magnification).
       
   423     self selectedColor = Color noColor
       
   424     ifTrue:
       
   425     [       
       
   426         self drawMaskPointAt: imagePoint * magnification + 1.
       
   427     ].
       
   428     self drawFrameAt: aPoint.
       
   429     self drawLabel: imagePoint.
       
   430     image restored.
       
   431     modified := true.
       
   432 !
       
   433 
       
   434 replaceAt: aPoint
       
   435 
       
   436     |imagePoint|
       
   437     imagePoint := aPoint//magnification.
       
   438     self selectedColor ~= Color noColor
       
   439     ifTrue:
       
   440     [   
       
   441         image mask notNil ifTrue: [image mask fillAround: imagePoint withColor: Color white].
       
   442         image fillAround: imagePoint withColor: self selectedColor.
       
   443         self paint: self selectedColor.
       
   444     ] 
       
   445     ifFalse:
       
   446     [
       
   447         image mask notNil ifTrue: [image mask fillAround: imagePoint withColor: Color black].
       
   448         self paint:self viewBackground.
       
   449     ].
       
   450     self drawLabel: imagePoint.
       
   451     self invalidate.
       
   452     image restored.
       
   453     modified := true.
       
   454 
       
   455 !
       
   456 
       
   457 undo
       
   458 
       
   459     undoImage notNil
       
   460     ifTrue:
       
   461     [
       
   462         modified := false.
       
   463         self image: undoImage.
       
   464         self invalidate
       
   465     ]
       
   466 ! !
       
   467 
       
   468 !ImageEditView methodsFor:'image editing'!
       
   469 
       
   470 flipHorizontal
       
   471 
       
   472     self image: image flipHorizontal.
       
   473 
       
   474 !
       
   475 
       
   476 flipVertical
       
   477 
       
   478     self image: image flipVertical.
       
   479 
       
   480 !
       
   481 
       
   482 negativeImage
       
   483 
       
   484     self image: image negative.
       
   485 
       
   486 !
       
   487 
       
   488 resizeImage
       
   489 
       
   490     |b newSize|
       
   491 
       
   492     b := EnterBox new.
       
   493     b title:'resize image'.
       
   494     b okText:'apply'.
       
   495     b abortText:'abort'.
       
   496     b initialText:image extent printString.
       
   497     b showAtPointer.
       
   498     (newSize := Object readFromString: b contents onError:nil) notNil
       
   499     ifTrue:
       
   500     [
       
   501         self image: (image magnifiedBy: newSize/image extent)
       
   502     ].
       
   503 !
       
   504 
       
   505 rotateImage
       
   506 
       
   507     |b rotation|
       
   508 
       
   509     b := EnterBox new.
       
   510     b title:'rotate image'.
       
   511     b okText:'apply'.
       
   512     b abortText:'abort'.
       
   513     b initialText: '0'.
       
   514     b showAtPointer.
       
   515     (rotation := Object readFromString: b contents onError:nil) notNil
       
   516     ifTrue:
       
   517     [   Object errorSignal handle:
       
   518         [:ex|
       
   519             WarningBox warn: 'Image rotation failed.\' withCRs, 'An increase of image depth could help.'.
       
   520         ] 
       
   521         do:
       
   522         [   
       
   523             self image: (image hardRotated: rotation)
       
   524         ]
       
   525     ].
       
   526 ! !
       
   527 
       
   528 !ImageEditView methodsFor:'image emphasis'!
       
   529 
       
   530 drawFrame
       
   531 
       
   532     self paint:Color black.
       
   533     "self lineWidth: (magnification x//3 min: 3). "
       
   534     self displayRectangle: ((0@0) extent:(image extent * magnification) + 2).
       
   535     self lineWidth:1.
       
   536 !
       
   537 
       
   538 drawFrameAt: aPoint
       
   539 
       
   540     magnification > gridMagnification
       
   541     ifTrue:
       
   542     [   
       
   543         |lineStartingPoint lineEndingPoint oldColor|
       
   544         lineStartingPoint := aPoint//magnification*magnification.
       
   545         lineEndingPoint   := aPoint//magnification*magnification + magnification.
       
   546         oldColor := self paint.
       
   547         self xoring:
       
   548         [
       
   549             self displayLineFrom: lineEndingPoint 
       
   550                               to: (lineEndingPoint x)@(lineStartingPoint y).
       
   551             self displayLineFrom: lineEndingPoint 
       
   552                               to: (lineStartingPoint x)@(lineEndingPoint y).
       
   553         ].
       
   554         self paint: oldColor.
       
   555     ]
       
   556 !
       
   557 
       
   558 drawLabel: aLabel
       
   559     coordInfoBlock notNil
       
   560     ifTrue:
       
   561     [         
       
   562         coordInfoBlock value: aLabel printString
       
   563     ]
       
   564 !
       
   565 
       
   566 drawMaskPointAt: aPoint
       
   567 
       
   568     |sizeOfMaskPoint|
       
   569     sizeOfMaskPoint := magnification//3.
       
   570     self xoring: [self fillRectangle: (aPoint + sizeOfMaskPoint extent: sizeOfMaskPoint)].
       
   571    
       
   572 ! !
       
   573 
       
   574 !ImageEditView methodsFor:'image setting'!
       
   575 
       
   576 image:anImage
       
   577 
       
   578     (anImage isImage and: [image isNil or: [self checkModified]])
       
   579     ifTrue:
       
   580     [
       
   581         super image: anImage.
       
   582         image photometric = #palette
       
   583         ifTrue:
       
   584         [
       
   585             (image usedColors includes: selectColors first) ifFalse: [selectColors at: 1 put: nil].
       
   586             (image usedColors includes: selectColors last) ifFalse: [selectColors at: 2 put: nil].
       
   587         ].
       
   588         ^self
       
   589     ].
       
   590     ^nil
       
   591 !
       
   592 
       
   593 loadFromFile: aFileName
       
   594 
       
   595     |fileName newImage|
       
   596     fileName := aFileName asFilename.
       
   597 
       
   598     Object errorSignal handle:
       
   599     [:exeption|
       
   600         WarningBox warn: exeption errorString.
       
   601         ^nil
       
   602     ] 
       
   603     do:
       
   604     [
       
   605         newImage := Image fromFile: fileName name.
       
   606     ].
       
   607 
       
   608     (self image: newImage) notNil
       
   609     ifTrue:
       
   610     [
       
   611         imageReaderClass := ImageReader allSubclasses detect: [:cls| cls isValidImageFile:fileName name] ifNone:
       
   612             [WarningBox warn: 'Unknown image file format'. ^nil].
       
   613     ]
       
   614 !
       
   615 
       
   616 resourceClass: aClassOrSymbol selector: aStringOrSymbol
       
   617 
       
   618     |aClass|
       
   619     imageReaderClass := nil.
       
   620     self resourceClass: aClassOrSymbol.
       
   621     self resourceSelector: aStringOrSymbol.
       
   622     aClass := Smalltalk at: resourceClass. 
       
   623     (aClass isClass and: [aClass class implements: resourceSelector])
       
   624     ifTrue:
       
   625     [ 
       
   626         ^self image: (aClass perform: resourceSelector) copy
       
   627     ].
       
   628     ^nil
       
   629 ! !
       
   630 
       
   631 !ImageEditView methodsFor:'initialization'!
       
   632 
       
   633 initialize
       
   634 
       
   635     super initialize.
       
   636 
       
   637     magnification := 1@1.
       
   638     gridMagnification := 8@8.
       
   639     modified := false.
       
   640     mouseKeyColorMode := 1.
       
   641     resourceClass := resourceSelector := ''.
       
   642     selectColors := Array with: nil with: nil.
       
   643     self menuHolder:self; menuPerformer:self; menuMessage:#imageMenu. 
       
   644 ! !
       
   645 
       
   646 !ImageEditView methodsFor:'menu actions'!
       
   647 
       
   648 changeMagnification
       
   649     |b newMag|
       
   650 
       
   651     b := EnterBox new.
       
   652     b title:'magnification (magX @ magY)'.
       
   653     b okText:'apply'.
       
   654     b abortText:'abort'.
       
   655     b action:[:string | newMag := (Object readFromString:string onError:nil)].
       
   656     b initialText:(magnification printString).
       
   657     b showAtPointer.
       
   658 
       
   659     newMag notNil ifTrue:[
       
   660         self magnification:newMag.
       
   661     ].
       
   662 
       
   663     "Modified: 31.7.1997 / 11:43:12 / cg"
       
   664 !
       
   665 
       
   666 loadFromClass
       
   667 
       
   668     self resourceMessage: (ResourceSelectionBrowser
       
   669         openOnSuperclass: ApplicationModel
       
   670         class: self resourceClass
       
   671         selector: self resourceSelector
       
   672         resourceTypes: #(#image #fileImage))
       
   673         
       
   674 
       
   675 !
       
   676 
       
   677 loadFromUser
       
   678 
       
   679     self image: 
       
   680         ((Image fromUser)
       
   681             asDitheredTrueColor8FormOn: Display)
       
   682 
       
   683 !
       
   684 
       
   685 print
       
   686     |stream psgc|
       
   687 
       
   688     image isNil ifTrue: [^nil].
       
   689 
       
   690     Printer supportsPostscript ifFalse:[
       
   691         self warn:'need a postscript printer'.
       
   692         ^ self
       
   693     ].
       
   694 
       
   695     stream := Printer newNative.
       
   696     stream isNil ifTrue:[
       
   697         self warn:'cannot open printer stream'.
       
   698         ^ nil
       
   699     ].
       
   700 
       
   701     self withWaitCursorDo:[
       
   702         psgc := PSGraphicsContext on:stream. "/  extent:(1.0 @ 1.0).
       
   703         psgc displayForm: (image magnifiedBy: magnification) x:0 y:0.
       
   704         psgc close.
       
   705     ]
       
   706 !
       
   707 
       
   708 save
       
   709 
       
   710     Object errorSignal handle:
       
   711     [:ex|
       
   712         WarningBox warn: ex errorString.
       
   713         ^nil                                 
       
   714     ] 
       
   715     do:
       
   716     [   
       
   717         |fileName|
       
   718         image isNil ifTrue: [^self error: 'No image to save!!'].
       
   719         image fileName isNil ifTrue: [^self error: 'No file name for image detected!!'].
       
   720         fileName := image fileName asFilename.
       
   721         (fileName suffix = 'tiff') | (fileName suffix = 'tif') ifTrue: [imageReaderClass := TIFFReader].
       
   722         fileName suffix = 'xpm' ifTrue: [imageReaderClass := XPMReader].
       
   723         fileName suffix = 'xbm' ifTrue: [imageReaderClass := XBMReader].
       
   724         fileName suffix = 'gif' ifTrue: [imageReaderClass := GIFReader].
       
   725         (fileName suffix = 'jpg') | (fileName suffix = 'jpeg') ifTrue: [imageReaderClass := JPEGReader].
       
   726         imageReaderClass isNil ifTrue: [imageReaderClass := XPMReader. image fileName: image fileName, '.xpm'].
       
   727         
       
   728         image saveOn: image fileName using: imageReaderClass.
       
   729         modified := false.
       
   730     ]
       
   731        
       
   732 !
       
   733 
       
   734 saveAs
       
   735     "save contents into a file 
       
   736      - ask user for filename using a fileSelectionBox."
       
   737 
       
   738     self saveImageFileAs
       
   739 !
       
   740 
       
   741 saveAsMethod
       
   742 
       
   743     Object errorSignal handle:
       
   744     [:ex|
       
   745         WarningBox warn: ex errorString.
       
   746         ^nil                                 
       
   747     ] 
       
   748     do:
       
   749     [   
       
   750         |compileString stream aClass|  
       
   751         stream := WriteStream on: ''.
       
   752         self resourceSelector trimBlanks size = 0 ifTrue: [^self error: 'No image selector detected'].
       
   753         (aClass := Smalltalk at: self resourceClass) isClass ifFalse: [^self error: 'No class for image selector detected'].
       
   754         self image storeOn: stream.
       
   755         compileString :=
       
   756             self resourceSelector,
       
   757             '\\' withCRs,
       
   758             '    <resource: #image>\' withCRs,
       
   759             '    ^',
       
   760             stream contents.   
       
   761         ByteCodeCompiler compile: compileString forClass: aClass class inCategory: 'resources'.
       
   762         modified := false.
       
   763     ]
       
   764 !
       
   765 
       
   766 saveImageFileAs
       
   767 
       
   768     |aFileName|
       
   769 
       
   770     (aFileName := (FileBrowserView requestFileName: self image fileName fileFilters: #('*.xpm' '*.gif'))) notNil
       
   771     ifTrue:
       
   772     [
       
   773         self saveImageFileAs: aFileName
       
   774     ].
       
   775 !
       
   776 
       
   777 saveImageFileAs: aFileName
       
   778 
       
   779     image notNil
       
   780     ifTrue:
       
   781     [
       
   782         image fileName: aFileName.
       
   783         self save
       
   784     ]
       
   785     ifFalse:
       
   786     [
       
   787         WarningBox warn: 'No image detected'
       
   788     ]
       
   789 ! !
       
   790 
       
   791 !ImageEditView methodsFor:'queries'!
       
   792 
       
   793 checkModified
       
   794 
       
   795     modified ifTrue:
       
   796     [
       
   797         |aBox|
       
   798         aBox := YesNoBox title:'Image was modified'.        
       
   799         aBox noText:'abort'.
       
   800         aBox yesText:'ignore'.
       
   801         aBox showAtPointer.
       
   802         aBox accepted ifFalse: [^false].
       
   803         modified := false
       
   804     ].
       
   805     ^true
       
   806 !
       
   807 
       
   808 heightOfContents
       
   809     "return the images height"
       
   810 
       
   811     image isNil ifTrue:[^ 0].
       
   812     ^ (image height * magnification y) rounded
       
   813 !
       
   814 
       
   815 imageContainsPoint: aPoint
       
   816     |pi|
       
   817     image isNil ifTrue: [^false].
       
   818     pi := ((aPoint - margin + 1) / magnification) floor.
       
   819     ^((0@0 corner:(image extent) - 1) containsPoint:pi)
       
   820 !
       
   821 
       
   822 widthOfContents
       
   823     "return the images width"
       
   824 
       
   825     image isNil ifTrue:[^ 0].
       
   826     ^ (image width * magnification x) rounded
       
   827 ! !
       
   828 
       
   829 !ImageEditView methodsFor:'release'!
       
   830 
       
   831 destroy
       
   832 
       
   833     undoImage := nil.
       
   834     Clipboard := nil.
       
   835     super destroy.
       
   836 
       
   837 ! !
       
   838 
       
   839 !ImageEditView class methodsFor:'documentation'!
       
   840 
       
   841 version
       
   842     ^ '$Header$'
       
   843 ! !