Rectangle.st
author claus
Tue, 11 Apr 1995 16:52:00 +0200
changeset 326 d2902942491d
parent 325 46bca6125b93
child 329 f14fc5ac11b7
permissions -rw-r--r--
*** empty log message ***

"
 COPYRIGHT (c) 1989 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-Geometry'
!

Rectangle comment:'
COPYRIGHT (c) 1989 by Claus Gittinger
	      All Rights Reserved

$Header: /cvs/stx/stx/libbasic/Rectangle.st,v 1.18 1995-04-11 14:51:30 claus Exp $
'!

!Rectangle class methodsFor:'documentation'!

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

version
"
$Header: /cvs/stx/stx/libbasic/Rectangle.st,v 1.18 1995-04-11 14:51:30 claus Exp $
"
!

documentation
"
    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

    I am not certain, if implementing Rectangle different was a good idea - 
    subclasses may expect things to be different ...
    Therefore, this may change.
"
! !

!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 */
    REGISTER OBJ newRect;
    extern OBJ Point;
    OBJ t;
    int spc;

    /* short cut - rectangles are created so often ... */
    if (_CanDoQuickNew(OHDR_SIZE + 4*sizeof(OBJ))) {
	if (self == Rectangle) {
	    if (__isPoint(origin) && __isPoint(extent)) {
		_qCheckedAlignedNew(newRect, OHDR_SIZE + 4*sizeof(OBJ));
		_InstPtr(newRect)->o_class = Rectangle;
		spc = __qSpace(newRect);

		t = _PointInstPtr(origin)->p_x;
		_InstPtr(newRect)->i_instvars[0] = t;
		__STORE_SPC(newRect, t, spc);

		t = _PointInstPtr(origin)->p_y;
		_InstPtr(newRect)->i_instvars[1] = t;
		__STORE_SPC(newRect, t, spc);

		t = _PointInstPtr(extent)->p_x;
		_InstPtr(newRect)->i_instvars[2] = t;
		__STORE_SPC(newRect, t, spc);

		t = _PointInstPtr(extent)->p_y;
		_InstPtr(newRect)->i_instvars[3] = t;
		__STORE_SPC(newRect, t, spc);
		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 */
    REGISTER OBJ newRect;
    OBJ t;
    int spc;

    if (_CanDoQuickNew(OHDR_SIZE + 4*sizeof(OBJ))) {
	if (self == Rectangle) {
	/* short cut - rectangles are created so often ... */
	    _qCheckedAlignedNew(newRect, OHDR_SIZE + 4*sizeof(OBJ));

	    _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;

	    if (! (__bothSmallInteger(left, top) && 
		   __bothSmallInteger(w, h))) {
		spc = __qSpace(newRect);
		__STORE_SPC(newRect, left, spc);
		__STORE_SPC(newRect, top, spc);
		__STORE_SPC(newRect, w, spc);
		__STORE_SPC(newRect, h, spc);
	    }

	    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
!

fromUser
    "let user specify a rectangle on the screen, return it"

    ^ Display rectangleFromUser

    "Rectangle fromUser"
! !

!Rectangle methodsFor:'accessing'!

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. The corner remains unchanged."

    |newTop newLeft|

    newTop := aPoint y.
    newLeft := aPoint x.
    height := height + (top - newTop).
    width := width + (left - newLeft).
    left := newLeft.
    top := newTop
!

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
!

left:aNumber
    "set the left edge"

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

right:aNumber
    "set the right edge"

    width := aNumber - left
!

topLeft:aPoint
    "Set the top and left edges.
     The bottom right remains unchanged."

    |newTop|

    newTop := aPoint y.
    height := height + (top - newTop).
    top := newTop.
    width := aPoint x - left
!

topRight:aPoint
    "Set the top and right edges. 
     The bottom left remains unchanged."

    |newTop|

    newTop := aPoint y.
    height := height + (top - newTop).
    top := newTop.
    width := aPoint x - left
!

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"

    ^ left @ top
!

corner
    "return the corner"

    ^ (left + width) @ (top + height)
!

width
    "return the width of the rectangle"

    ^ width
!

height
    "return the height of the rectangle"

    ^ height
!

extent
    "return the extent"

    ^ width @ height
!

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

    ^ left
!

leftCenter
    "return the left center point"

    ^ left @ (top + (height // 2))
!

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

    ^ top
!

topLeft
    "return the top-left point - the same as origin"

    ^ left @ top
!

topRight
    "return the top-right point"

    ^ (left + width) @ top
!

topCenter
    "return the top center point"

    ^ (left + (width // 2)) @ top
!

bottom
    "return the y coordinate of the bottom"

    ^ (top + height)
!

bottomLeft
    "return the bottom-left point"

    ^ left @ (top + height)
!

bottomRight
    "return the bottom-right point"

    ^ (left + width) @ (top + height)
!

bottomCenter
    "return the bottom center point"

    ^ (left + (width // 2)) @ (top + height)
!

right
    "return the x coordinate of the right"

    ^ (left + width)
!

rightCenter
    "return the right center point"

    ^ (left + width) @ (top + (height // 2))
!

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

    ^ (left + (width // 2)) @ (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 */
    /*
     * handle the common case quickly
     */
    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 );
	}
	if (__bothSmallInteger(_InstPtr(self)->i_instvars[0], _InstPtr(aRectangle)->i_instvars[0])
	 && __bothSmallInteger(_InstPtr(self)->i_instvars[1], _InstPtr(aRectangle)->i_instvars[1])
	 && __bothSmallInteger(_InstPtr(self)->i_instvars[2], _InstPtr(aRectangle)->i_instvars[2])
	 && __bothSmallInteger(_InstPtr(self)->i_instvars[3], _InstPtr(aRectangle)->i_instvars[3])) {
	    RETURN ( false );
	}
    }
%}
.
    (aRectangle species ~~ self species) ifTrue:[^ false].

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

hash
    "return an integer useful for hashing -
     redefined since = is redefined here"

    ^ ((left hash bitShift:16) bitXor:(top hash bitShift:16))
      + ((width hash) bitXor:(height hash))
! !

!Rectangle methodsFor:'queries'!

isRectangle
    "return true, if the receiver is some kind of rectangle"

    ^ 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
!

containsPointX:x y:y
    "return true, if the point defined by x@y is contained in the receiver.
     This is the same as containsPoint:, but can be used if the coordinates
     are already available as separate numbers to avoid useless creation of a
     temporary point."

    (x < left)           ifTrue:[^ false].
    (x > (left + width)) ifTrue:[^ false].
    (y < top)            ifTrue:[^ false].
    (y > (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:'destructive rectangle operations'!

translateBy:amount
    "translate (i.e. move) the receiver rectangle 
     by amount, a Point or Number.
     This is destructive (modifies the receiver, not a copy) and 
     should only be used if you know, that you are the exclusive owner 
     of the receiver. (use translatedBy if in doubt)"

    |amountPoint|

    (amount isMemberOf:Point) ifTrue:[  "type hint to stc"
	left := left + amount x.
	top := top + amount y
    ] ifFalse:[
	amountPoint := amount asPoint.
	left := left + amountPoint x.
	top := top + amountPoint y
    ]

    "
     (Rectangle origin:10@10 corner:50@50) translateBy:10
    "

    "its destructive:"
    "
     |r1 r2|

     r1 := Rectangle origin:10@10 corner:50@50.
     r2 := r1 translateBy:10.
     r1 
    "
!

scaleBy:scale
    "scale the receiver rectangle by scale (a Number or Point).
     This is destructive (modifies the receiver, not a copy) and 
     should only be used if you know, that you are the exclusive owner 
     of the receiver. (use scaledBy if in doubt)"

    |scalePoint sx sy|

    (scale isMemberOf:Point) ifTrue:[  "type hint to stc"
	sx := scale x.
	sy := scale y
    ] ifFalse:[
	scalePoint := scale asPoint.
	sx := scalePoint x.
	sy := scalePoint y
    ].
    width := width * sx.
    height := height * sy.
    left := left * sx.
    top := top * sy

    "
     (Rectangle origin:10@10 corner:50@50) scaleBy:2 
    "

    "its destructive:"
    "
     |r1 r2|

     r1 := Rectangle origin:10@10 corner:50@50.
     r2 := r1 scaleBy:2.
     r1 
    "
!

moveTo:aPoint
    "destructively translate the rectangle to have its origin at aPoint."

    |diff|

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

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

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

!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))

    "
     |r1 r2|

     r1 := Rectangle origin:10@10 corner:100@100.
     r2 := Rectangle origin:50@50 corner:150@75.
     r1 intersect:r2
    "
!

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"

    |amountPoint|

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

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

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

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

    |amountPoint deltaLeft deltaTop deltaWidth deltaHeight|

    delta isNumber ifTrue:[
	deltaLeft := deltaTop := delta.
	deltaWidth := deltaHeight := delta * 2.
    ] ifFalse:[
	delta isRectangle ifTrue:[
	    deltaLeft := delta left.
	    deltaTop := delta top.
	    deltaWidth := deltaLeft + delta right.
	    deltaHeight := deltaTop + delta bottom
	] ifFalse:[
	    amountPoint := delta asPoint.
	    deltaLeft := amountPoint x.
	    deltaTop := amountPoint y.
	    deltaWidth := deltaLeft * 2.
	    deltaHeight := deltaTop * 2.
	]
    ].

    ^ Rectangle left:(left - deltaLeft)
		 top:(top - deltaTop)
	       width:(width + deltaWidth)
	      height:(height + deltaHeight)

    "
     |r|
     r := Rectangle origin:10@10 corner:100@100.
     r expandBy:5.
     r expandBy:(5 @ 0).
     r expandBy:(10 @ 10).
     r expandBy:( 10@10 corner:20@20 )
    "
!

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

    |amountPoint deltaLeft deltaTop deltaWidth deltaHeight|

    delta isNumber ifTrue:[
	deltaLeft := deltaTop := delta.
	deltaWidth := deltaHeight := delta * 2.
    ] ifFalse:[
	delta isRectangle ifTrue:[
	    deltaLeft := delta left.
	    deltaTop := delta top.
	    deltaWidth := deltaLeft + delta right.
	    deltaHeight := deltaTop + delta bottom
	] ifFalse:[
	    amountPoint := delta asPoint.
	    deltaLeft := amountPoint x.
	    deltaTop := amountPoint y.
	    deltaWidth := deltaLeft * 2.
	    deltaHeight := deltaTop * 2.
	]
    ].

    ^ Rectangle left:(left + deltaLeft)
		 top:(top + deltaTop)
	       width:(width - deltaWidth)
	      height:(height - deltaHeight)
    "
     |r|
     r := Rectangle origin:10@10 corner:100@100.
     r insetBy:5.
     r insetBy:(5 @ 0).
     r insetBy:(10 @ 10).
     r insetBy:( 10@10 corner:20@20 )
    "
!

translatedBy: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
    "
     (Rectangle origin:10@10 corner:50@50) translatedBy:10
    "

    "its NOT destructive:"
    "
     |r1 r2|

     r1 := Rectangle origin:10@10 corner:50@50.
     r2 := r1 translatedBy:10.
     r1 
    "
!

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

    |scalePoint sx sy|

    scalePoint := scale asPoint.
    sx := scalePoint x.
    sy := scalePoint y.
    ^ Rectangle left:left * sx
		 top:top * sy
	       width:(width * sx)
	      height:(height * sy)
    "
     (Rectangle origin:10@10 corner:50@50) scaledBy:2   
    "

    "its NOT destructive:"
    "
     |r1 r2|

     r1 := Rectangle origin:10@10 corner:50@50.
     r2 := r1 scaledBy:2.    
     r1  
    "
!

align:offset with:someCoordinate
    "return a new rectangle which is translated (i.e. moved)
     such that the point offset in mySelf is placed on someCoordinate."

    ^ Rectangle origin:(someCoordinate - offset + self origin)
		extent:(self extent)
    "
     |r|

     r := Rectangle origin:10@10 corner:50@50.
     r align:(r center) with:100@100.
    "
!

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) or: [(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) or: [(iRect bottom) ~= self bottom])
	ifTrue:                 "whole bottom open and can be taken"
	    [tmp _ Rectangle origin: iRect bottomLeft corner: self corner.
		 collect add: tmp].
    ^collect
!

nonIntersections:aRectangle
    "this is the same as areasOutside: - for ST/V compatibility only"

    ^ self areasOutside:aRectangle
! !

!Rectangle methodsFor:'printing & storing'!

printOn:aStream
    "print the receiver on aStream"

    aStream nextPutAll:(self class name).
    aStream nextPutAll:' 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 nextPut:$(.
    aStream nextPutAll:(self class name).
    aStream nextPutAll:' origin:'.
    (self origin) storeOn:aStream.
    aStream nextPutAll:' corner:'.
    (self corner) storeOn:aStream.
    aStream nextPut:$)
! !