Rectangle.st
author claus
Fri, 16 Jul 1993 11:39:45 +0200
changeset 1 a27a279701f8
child 2 6526dde5f3ac
permissions -rw-r--r--
Initial revision

"
 COPYRIGHT (c) 1989-92 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.
"

Object subclass:#Rectangle
       instanceVariableNames:'left top width height'
       classVariableNames:''
       poolDictionaries:''
       category:'Graphics-Primitives'
!

Rectangle comment:'

COPYRIGHT (c) 1989-92 by Claus Gittinger
              All Rights Reserved

Rectangles represent a rectangular area in 2D space.

notice, my implementation does not use origin/corner as instance objects
but left/top/width/height to save space and allocations. This means, that my
Rectangles cannot be used to represent Rectangles in a higher than 2D
space. (i.e. only valid if origin/corner are 2D Points)

(aside from that, you will not see any difference from the outside)

Instance variables:

left           <Number>        the left coordinate (i.e origin x)
top            <Number>        the top coordinate (i.e origin y)
width          <Number>        the width of the rectangle
height         <Number>        the height of the rectangle

%W% %E%

written 89 by claus
'!

!Rectangle class methodsFor:'instance creation'!

origin:origin corner:corner
    "create and return a new Rectangle giving top-left and bottom-right points"

    ^ (self basicNew) origin:origin corner:corner
!

origin:origin extent:extent
    "create and return a new Rectangle giving top-left point and extent point"

%{  /* NOCONTEXT */
    OBJ newRect;
    extern char *newNextPtr, *newEndPtr;
    extern OBJ Point;

    /* short cut - rectangles are created so often ... */
    if (_CanDoQuickNew(OHDR_SIZE + 4*sizeof(OBJ))) {
        if ((self == Rectangle) 
         && _isPoint(origin) 
         && _isPoint(extent)) {
            _qCheckedAlignedNew(newRect, OHDR_SIZE + 4*sizeof(OBJ), __context);
            _InstPtr(newRect)->o_class = Rectangle;
            _InstPtr(newRect)->i_instvars[0] = _PointInstPtr(origin)->p_x;
            _InstPtr(newRect)->i_instvars[1] = _PointInstPtr(origin)->p_y;
            _InstPtr(newRect)->i_instvars[2] = _PointInstPtr(extent)->p_x;
            _InstPtr(newRect)->i_instvars[3] = _PointInstPtr(extent)->p_y;
            /* no STOREs needed - newRect is in newSpace */
            RETURN ( newRect );
        }
    }
%}
.
    ^ (self basicNew) origin:origin extent:extent
!

left:left top:top width:w height:h
    "create and return a new Rectangle giving left and top coordinates
     and width, height"

%{  /* NOCONTEXT */
    OBJ newRect;
    extern char *newNextPtr, *newEndPtr;

    if (_CanDoQuickNew(OHDR_SIZE + 4*sizeof(OBJ))) {
        /* short cut - rectangles are created so often ... */
        if (self == Rectangle) {
            _qCheckedAlignedNew(newRect, OHDR_SIZE + 4*sizeof(OBJ), __context);
            _InstPtr(newRect)->o_class = Rectangle;
            _InstPtr(newRect)->i_instvars[0] = left;
            _InstPtr(newRect)->i_instvars[1] = top;
            _InstPtr(newRect)->i_instvars[2] = w;
            _InstPtr(newRect)->i_instvars[3] = h;
            /* no STOREs needed - newRect is in newSpace */
            RETURN ( newRect );
        }
    }
%}
.
    ^ (self basicNew) left:left top:top width:w height:h
!

left:left right:right top:top bottom:bottom
    "create and return a new Rectangle giving left, top, right and bottom coordinates"

    ^ (self basicNew) left:left right:right top:top bottom:bottom
!

left:left top:top right:right bottom:bottom
    "create and return a new Rectangle giving left, top, right and bottom coordinates"

    ^ (self basicNew) left:left top:top right:right bottom:bottom
! !

!Rectangle methodsFor:'accessing'!

top
    "return the y-coordinate of the top-left origin"

    ^ top
!

left
    "return the x-coordinate of the top-left origin"

    ^ left
!

width
    "return the width of the rectangle"

    ^ width
!

height
    "return the height of the rectangle"

    ^ height
!

left:newLeft right:right top:newTop bottom:bottom
    "set the rectangle given left, top, right and bottom coordinates"

    left := newLeft.
    top := newTop.
    width := right - left.
    height := bottom - top
!

left:newLeft top:newTop right:right bottom:bottom
    "set the rectangle given left, top, right and bottom coordinates"

    left := newLeft.
    top := newTop.
    width := right - left.
    height := bottom - top
!

left:newLeft top:newTop width:newWidth height:newHeight
    "set the rectangle given left, top coordinates and width, height"

    left := newLeft.
    top := newTop.
    width := newWidth.
    height := newHeight
!

origin:aPoint
    "set the top-left origin"

    left := aPoint x.
    top := aPoint y
!

corner:aPoint
    "set the bottom-right corner"

    width := aPoint x - left.
    height := aPoint y - top
!

top:aNumber
    "set the top edge"

    height := height + (top - aNumber).
    top := aNumber
!

bottom:aNumber
    "set the bottom edge"

    height := aNumber - top
!

origin:origin corner:corner
    "set both origin and corner"

    left := origin x.
    top := origin y.
    width := corner x - left.
    height := corner y - top
!

extent:aPoint
    "set the extent from the argument, aPoint with width taken from aPoint x
     and height taken from aPoint y"

    width := aPoint x.
    height := aPoint y
!

origin:origin extent:extent
    "set both origin and extent"

    left := origin x.
    top := origin y.
    width := extent x.
    height := extent y
!

origin
    "return the origin"

    ^ Point x:left y:top
!

left:aNumber
    "set the left edge"

    width := width + (left - aNumber).
    left := aNumber
!

right:aNumber
    "set the right edge"

    width := aNumber - left
!

corner
    "return the corner"

    ^ Point x:(left + width) y:(top + height)
!

extent
    "return the extent"

    ^ Point x:width y:height
!

topLeft
    "return the top-left point"

    ^ Point x:left y:top
!

topRight
    "return the top-right point"

    ^ Point x:(left + width) y:top
!

bottomLeft
    "return the bottom-left point"

    ^ Point x:left y:(top + height)
!

bottomRight
    "return the bottom-right point"

    ^ Point x:(left + width) y:(top + height)
!

bottom
    "return the y coordinate of the bottom"

    ^ (top + height)
!

right
    "return the x coordinate of the right"

    ^ (left + width)
!

center
    "return the point in the center of the receiver"

    ^ Point x:(left + (width // 2)) y:(top + (height // 2))
!

leftCenter
    "return the left center point"

    ^ Point x:left y:(top + (height // 2))
!

rightCenter
    "return the right center point"

    ^ Point x:(left + width) y:(top + (height // 2))
!

area
    "return the area (- for screen Rectangles this is the number
     of pixels)"

    ^ width * height
! !

!Rectangle methodsFor:'comparing'!

= aRectangle
    "return true, if the argument aRectangle represents the same
     rectangle as the receiver"

%{  /* NOCONTEXT */
    static struct inlineCache eq = _ILC1;

    if (_isNonNilObject(aRectangle) && _qClass(aRectangle) == Rectangle) {
        if (( _InstPtr(self)->i_instvars[0] == _InstPtr(aRectangle)->i_instvars[0] )
         && ( _InstPtr(self)->i_instvars[1] == _InstPtr(aRectangle)->i_instvars[1] )
         && ( _InstPtr(self)->i_instvars[2] == _InstPtr(aRectangle)->i_instvars[2] )
         && ( _InstPtr(self)->i_instvars[3] == _InstPtr(aRectangle)->i_instvars[3] )) {
            RETURN ( true );
        }
    }
%}
.
    (aRectangle isKindOf:Rectangle) ifFalse:[^ false].

    left = aRectangle left ifFalse:[^ false].
    top = aRectangle top ifFalse:[^ false].
    width = aRectangle width ifFalse:[^ false].
    height = aRectangle height ifFalse:[^ false].
    ^ true
! !

!Rectangle methodsFor:'testing'!

containsPoint:aPoint
    "return true, if the argument, aPoint is contained in the receiver"

    |px py|

    px := aPoint x.
    (px < left)           ifTrue:[^ false].
    (px > (left + width)) ifTrue:[^ false].
    py := aPoint y.
    (py < top)            ifTrue:[^ false].
    (py > (top + height)) ifTrue:[^ false].
    ^ true
!

intersects:aRectangle
    "return true, if the intersection between the argument, aRectangle
     and the receiver is not empty"

    |b r|

    (aRectangle right)  < left ifTrue:[^ false].
    (aRectangle bottom) < top  ifTrue:[^ false].
    r := left + width.
    (aRectangle left)   > r    ifTrue:[^ false].
    b := top + height.
    (aRectangle top)    > b    ifTrue:[^ false].
    ^ true
!

contains:aRectangle
    "return true, if the argument, aRectangle is equal to or
     is contained fully within the receiver"

    (left <= aRectangle left) ifTrue:[
      ((left + width) >= aRectangle right) ifTrue:[
        (top <= aRectangle top) ifTrue:[
          ((top + height) >= aRectangle bottom) ifTrue:[
            ^ true
          ]
        ]
      ]
    ].
    ^ false
!

isContainedIn:aRectangle
    "return true, if the receiver is fully contained within 
     the argument, aRectangle"

    (aRectangle left <= left) ifTrue:[
      (aRectangle right >= (left + width)) ifTrue:[
        (aRectangle top <= top) ifTrue:[
          (aRectangle bottom >= (top + height)) ifTrue:[
            ^ true
          ]
        ]
      ]
    ].
    ^ false
! !

!Rectangle methodsFor:'rectangle operations'!

intersect:aRectangle
    "return a new rectangle covering the intersection of the receiver
     and the argument, aRectangle.
     the rectangles must intersect for a valid return"

    ^ Rectangle left:(left max:(aRectangle left))
               right:((left + width) min:(aRectangle right))
                 top:(top max:(aRectangle top))
              bottom:((top + height) min:(aRectangle bottom))
!

merge:aRectangle
    "return a new rectangle covering both the receiver 
     and the argument, aRectangle"

    ^ Rectangle left:(left min:(aRectangle left))
               right:((left + width) max:(aRectangle right))
                 top:(top min:(aRectangle top))
              bottom:((top + height) max:(aRectangle bottom))
!

+ aPoint
    "return a Rectangle with same extent as receiver but
     origin translated by the argument, aPoint"

    ^ Rectangle origin:(self origin + aPoint) extent:(self extent)
!

rounded
    ^ Rectangle left:(left rounded) top:(top rounded)
               width:(width rounded) height:(height rounded)
!

expandBy:amount
    "return a new rectangle which is expanded in all directions
     by amount, aPoint or Number"

    |amountPoint|

    amountPoint := amount asPoint.
    ^ Rectangle left:(left - amountPoint x) top:(top - amountPoint y)
               width:(width + (2 * amountPoint x))
              height:(height + (2 * amountPoint y))
!

insetBy: delta
    "return a new rectangle which is inset in all directions
     by delta, aPoint or Rectangle"

    | newrect |

    newrect := delta asRectangle.
    ^Rectangle origin: (self origin + (newrect origin))
               corner: (self corner - (newrect corner))
!

translateBy:amount
    "return a new rectangle which is translated (i.e. moved)
     by amount, aPoint or Number"

    |amountPoint|

    amountPoint := amount asPoint.
    ^ Rectangle left:(left + amountPoint x) top:(top + amountPoint y)
               width:(width)
              height:(height)
!

moveTo: aPoint
    "destructively translate the rectangle"

    | diff |

    diff := aPoint - self origin.
    self origin:aPoint corner:self corner + diff
!

moveBy: aPoint
    "destructively translate the rectangle
     sorry for the name inconsistency - but GNU-ST named it that way"

    left := left + aPoint x.
    top := top + aPoint y
!

scaleBy:scale
    "destructively scale the receiver rectangle by scale"

    |scalePoint|

    scalePoint := scale asPoint.
    width := (width * scalePoint x).
    height := (height * scalePoint y)
!

scaledBy:scale
    "return a new rectangle which is the receiver
     scaled by scale"

    |scalePoint|

    scalePoint := scale asPoint.
    ^ Rectangle left:left top:top
               width:(width * scalePoint x)
              height:(height * scalePoint y)
!

amountToTranslateWithin: aRectangle
    "for GNU-ST compatibility"

    ^(aRectangle origin) - self origin
!

areasOutside: aRectangle
    "----------------------------------------------------------------
    | added for GNU-ST compatibility
    |
    | author: Doug McCallum <uunet!!ico.isc.com!!dougm>
    |
    |areasOutside: aRectangle
    | most complicated of the Rectangle primitives
    | The basic methodology is to first determine that there is an 
    | intersection by finding the overlapping rectangle.  From the
    | overlapping rectangle, first determine if it runs along an edge.
    | If it doesn't, extend the rectangle up to the top edge and add
    | the new rectangle to the collection and start the rest of the
    | process.  If the left edge does not touch the left edge of self,
    | extend it to the edge saving the new rectangle.  Then do the 
    | same to the right edge.  Then check top and bottom edges.  Most
    | of the time only 2 or 3 rectangles get formed, occasionally 4.
    | It should be possible to never get more than 3 but requires more
    | work.
     ----------------------------------------------------------------"

    | collect iRect tmp |
    iRect _ self intersect: aRectangle.
    (iRect = nil) ifTrue: [^nil]. "case of no intersection"
                                "the collect collection gathers Rectangles"
    collect _ OrderedCollection new: 4.
                                "is it floating or on the edge?"
    (((((iRect top) ~= self top) 
         and: [ (iRect bottom) ~= self bottom ])
         and: [ (iRect left) ~= self left ])
         and: [ (iRect right) ~= self right ] )
        ifTrue: "entirely in the center."
            [tmp _ Rectangle origin: (Point x: iRect left y: self top)
                             corner: iRect bottomRight.
             collect add: tmp.
             iRect _ iRect merge: tmp].
    ((iRect left) ~= self left)
        ifTrue:                 "doesn't touch left edge so make it touch"
            [tmp _ Rectangle origin: (Point x: self left y: iRect top)
                                 corner: iRect bottomLeft.
                 collect add: tmp.
                                "merge new (tmp) with overlap to keep track"
                 iRect _ iRect merge: tmp].
    ((iRect right) ~= self right)
        ifTrue:                 "doesn't touch right edge so extend it"
            [tmp _ Rectangle origin: iRect topRight
                                 corner: (Point x: self right y: iRect bottom).
                 collect add: tmp.
                 iRect _ iRect merge: tmp].
    (((iRect left) ~= self left) || [(iRect top) ~= self top])
        ifTrue:                 "whole top part can be taken now"
            [tmp _ Rectangle origin: self origin corner: iRect topRight.
                 collect add: tmp].
    (((iRect right) ~= self right) || [(iRect bottom) ~= self bottom])
        ifTrue:                 "whole bottom open and can be taken"
            [tmp _ Rectangle origin: iRect bottomLeft corner: self corner.
                 collect add: tmp].
    ^collect

! !

!Rectangle methodsFor:'printing'!

printString
    "return a string for printing"

    ^ 'Rectangle origin:'
      , self origin printString
      , ' corner:'
      , self corner printString
!

printOn:aStream
    "print the receiver on aStream"

    aStream nextPutAll:'Rectangle origin:'.
    (self origin) printOn:aStream.
    aStream nextPutAll:' corner:'.
    (self corner) printOn:aStream
!

storeOn:aStream
    "store the receiver on aStream; i.e. print an expression which will
     reconstruct the receiver"

    aStream nextPutAll:'('.
    aStream nextPutAll:(self class name).
    aStream nextPutAll:' new origin:'.
    aStream nextPutAll:(self origin printString).
    aStream nextPutAll:' corner:'.
    aStream nextPutAll:(self corner printString).
    aStream nextPutAll:'('
! !