Point.st
author claus
Tue, 16 May 1995 19:09:45 +0200
changeset 345 cf2301210c47
parent 339 e8658d38abfb
child 356 6c5ce0e1e7a8
permissions -rw-r--r--
.

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

ArithmeticValue subclass:#Point
       instanceVariableNames:'x y'
       classVariableNames:'PointZero PointOne'
       poolDictionaries:''
       category:'Graphics-Geometry'
!

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

$Header: /cvs/stx/stx/libbasic/Point.st,v 1.22 1995-05-16 17:08:22 claus Exp $
'!

!Point 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/Point.st,v 1.22 1995-05-16 17:08:22 claus Exp $
"
!

documentation
"
    I represent a point in 2D space. Or I can be used to represent
    an extent (of a rectangle, for example), in which case my x-coordinate 
    represents the width, and y-coordinate the height of something.

    The x and y coordinate are usually numbers.

    Instance variables:

	x              <Number>        the x-coordinate of myself
	y              <Number>        the y-coordinate of myself
"
! !

!Point class methodsFor:'initialization'!

initialize
    PointZero isNil ifTrue:[
	PointZero := 0 @ 0.
	PointOne  := 1 @ 1
    ]
! !

!Point class methodsFor:'constants'!

zero
    "return the neutral element for addition"

    ^ PointZero
!

unity
    "return the neutral element for multiplication"

    ^ PointOne
! !

!Point class methodsFor:'queries'!

isBuiltInClass
    "this class is known by the run-time-system"

    ^ self == Point
! !

!Point class methodsFor:'instance creation'!

x:newX y:newY
    "create and return a new point with coordinates newX and newY"

%{  /* NOCONTEXT */

    /*
     * claus: I am no longer certain, if this primitive is worth the effort
     */
    if (_CanDoQuickNew(sizeof(struct __point))) {
	if (self == Point) {
	    OBJ newPoint;
	    int spc;

	    _qCheckedAlignedNew(newPoint, sizeof(struct __point));
	    _InstPtr(newPoint)->o_class = Point;
	    _PointInstPtr(newPoint)->p_x = newX;
	    _PointInstPtr(newPoint)->p_y = newY;
	    if (! __bothSmallInteger(newX, newY)) {
		spc = __qSpace(newPoint);
		__STORE_SPC(newPoint, newX, spc);
		__STORE_SPC(newPoint, newY, spc);
	    }
	    RETURN ( newPoint );
	}
    }
%}
.
    ^ (self basicNew) x:newX y:newY
!

readFrom:aStream onError:exceptionBlock
    "return the next Point from the (character-)stream aStream;
     skipping all whitespace first; return the value of exceptionBlock,
     if no point can be read."

    |newX newY|

    newX := Number readFrom:aStream onError:nil.
    newX notNil ifTrue:[
	(aStream skipSeparators == $@) ifTrue:[
	    aStream next.
	    newY := Number readFrom:aStream onError:nil.
	    newY notNil ifTrue:[
		^ (self basicNew) x:newX y:newY
	    ]
	]
    ].
    ^ exceptionBlock value

    "
     Point readFrom:('1.234 @ 5.678' readStream)
     Point readFrom:('1' readStream)
     Point readFrom:('1' readStream) onError:[1@1]
     Point readFrom:('fooBar' readStream) onError:[0@0]
    "  
! !

!Point methodsFor:'accessing'!

x
    "return the x coordinate"

    ^ x
!

y
    "return the y coordinate"

    ^ y
!

x:newX
    "set the x coordinate to be the argument, aNumber.
     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."

    x := newX
!

y:newY
    "set the y coordinate to be the argument, aNumber.
     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."

    y := newY
!

x:newX y:newY
    "set both the x and y coordinates.
     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."

    x := newX.
    y := newY
! !

!Point methodsFor:'comparing'!

hash
    "return a number for hashing"

    x = y ifTrue:[^ x hash].
"
 used to be:
    ^ (x hash) bitXor:(y hash)
 the following handles 1@x vs. x@1 better:
"
    ^ (x hash) bitXor:(y hash bitShift:12)
!

< aPoint
    "return true if the receiver is above and to the left
     of the argument, aPoint"

    |p|

    p := aPoint asPoint.
    x >= (p x) ifTrue:[^ false].
    y >= (p y) ifTrue:[^ false].
    ^ true
!

> aPoint
    "return true if  the receiver is below and to the right
     of the argument, aPoint"

    |p|

    p := aPoint asPoint.
    x <= (p x) ifTrue:[^ false].
    y <= (p y) ifTrue:[^ false].
    ^ true
!

= aPoint
    "return true if the receiver represents the same point as
     the argument, aPoint"

    |p|

    (aPoint isMemberOf:Point) ifTrue:[     "this is a hint to STC"
	x ~= (aPoint x) ifTrue:[^ false].
	y ~= (aPoint y) ifTrue:[^ false].
	^ true
    ].
    aPoint respondsToArithmetic ifFalse:[ ^ false].
    p := aPoint asPoint.
    x ~= (p x) ifTrue:[^ false].
    y ~= (p y) ifTrue:[^ false].
    ^ true
!

max:aPoint
    "return the lower right corner of the rectangle uniquely defined by
     the receiver and the argument, aPoint"

    |p maxX maxY|

    p := aPoint asPoint.
    maxX := x max:(p x).
    maxY := y max:(p y).
    ^ maxX @ maxY
!

min:aPoint
    "return the upper left corner of the rectangle uniquely defined by
     the receiver and the argument, aPoint"

    |p minX minY|

    p := aPoint asPoint.
    minX := x min:(p x).
    minY := y min:(p y).
    ^ minX @ minY
! !

!Point methodsFor:'coercing & converting'!

generality
    "return the generality value - see ArithmeticValue>>retry:coercing:"

    ^ 120
!

coerce:anObject
    "return aNumber converted into receivers type"

    ^ anObject asPoint
!

asPoint
    "return the receiver as Point - this is the receiver"

    ^ self
!

asRectangle
    "return a zero-width rectangle consisting of origin 
     and corner being the receiver"

    ^ self corner:self
!

asLayout
    "return a LayoutOrigin from the receiver.
     If the receiver coordinates are between 0 and 1, take
     them as fractional parts (relative to superview).
     Otherwise, treat them as absolute offsets.
     Notice: in 10.5.x LayoutOrigin is not yet released."

    ^ LayoutOrigin fromPoint:self
!

asFractionalLayout
    "return a LayoutOrigin from the receiver,
     treating the receiver coordinates as fractional parts 
     (i.e. relative to superview).
     Notice: in 10.5.x LayoutOrigin is not yet released."

    ^ LayoutOrigin fractionalFromPoint:self
!

asOffsetLayout
    "return a LayoutOrigin from the receiver,
     treating the receiver coordinates as absolute offsets. 
     Notice: in 10.5.x LayoutOrigin is not yet released."

    ^ LayoutOrigin offsetFromPoint:self
! !

!Point methodsFor:'creating rectangles'!

corner:aPoint
    "return a rectangle whose origin is self and corner is aPoint"

    ^ Rectangle origin:self corner:aPoint
!

extent:aPoint
    "return a rectangle whose origin is self and extent is aPoint"

    ^ Rectangle origin:self extent:aPoint
! !

!Point methodsFor:'transformations'!

+ scale 
    "Return a new Point that is the sum of the 
     receiver and scale (which is a Point or Number)."

    |scalePoint|

    "speedup for common cases ..."

    (scale isMemberOf:Point) ifTrue:[     
	^ (x + scale x) @ (y + scale y)
    ].
    (scale isMemberOf:SmallInteger) ifTrue:[
	^ (x + scale) @ (y + scale)
    ].
    scale isNumber ifTrue:[
	^ (x + scale) @ (y + scale)
    ].

    "this is the general (& clean) code ..."

    scalePoint := scale asPoint.
    ^ (x + scalePoint x) @ (y + scalePoint y)
!

- scale 
    "Return a new Point that is the difference of the 
     receiver and scale (which is a Point or Number)."

    |scalePoint|

    "speedup for common cases ..."

    (scale isMemberOf:Point) ifTrue:[     
	^ (x - scale x) @ (y - scale y)
    ].
    (scale isMemberOf:SmallInteger) ifTrue:[
	^ (x - scale) @ (y - scale)
    ].
    scale isNumber ifTrue:[
	^ (x - scale) @ (y - scale)
    ].

    "this is the general (& clean) code ..."

    scalePoint := scale asPoint.
    ^ (x - scalePoint x) @ (y - scalePoint y)
!

* scale 
    "Return a new Point that is the product of the 
     receiver and scale (which is a Point or Number)."

    |scalePoint|

    "speedup for common cases ..."

    (scale isMemberOf:Point) ifTrue:[    
	^ (x * scale x) @ (y * scale y)
    ].
    (scale isMemberOf:SmallInteger) ifTrue:[
	^ (x * scale) @ (y * scale)
    ].
    scale isNumber ifTrue:[
	^ (x * scale) @ (y * scale)
    ].

    "this is the general (& clean) code ..."

    scalePoint := scale asPoint.
    ^ (x * scalePoint x) @ (y * scalePoint y)
!

/ scale 
    "Return a new Point that is the integer quotient of the 
     receiver and scale (which is a Point or Number)."

    |scalePoint|

    "speedup for common cases ..."

    (scale isMemberOf:Point) ifTrue:[    
	^ (x / scale x) @ (y / scale y)
    ].
    scale isNumber ifTrue:[
	^ (x / scale) @ (y / scale)
    ].

    "this is the general (& clean) code ..."

    scalePoint := scale asPoint.
    ^ (x / scalePoint x) @ (y / scalePoint y)
!

// scale 
    "Return a new Point that is the quotient of the 
     receiver and scale (which is a Point or Number)."

    |scalePoint|

    scalePoint := scale asPoint.
    ^ (x // scalePoint x) @ (y // scalePoint y)
!

reciprocal
    "return a new point where the coordinates are
     the reciproce of mine"

    ^ (1 / x) @ (1 / y)
!

negated
    "return a new point with my coordinates negated 
     i.e. the receiver mirrored at the origin"

    ^ (x negated) @ (y negated)
! 

scaledBy:aScale
    "return a new Point that is the product of the 
     receiver and scale (which is a Point or Number)."

    ^ self * aScale
!

translatedBy:anOffset
    "return a new Point that is the sum of the 
     receiver and scale (which is a Point or Number)."

    ^ self + anOffset
! !

!Point methodsFor:'destructive transformations'!

scaleBy:aScale
    "scale the receiver, by replacing coordinates by the product
     of the receivers coordinates and the scale (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."

    |scalePoint|

    (aScale isMemberOf:Point) ifTrue:[  "type hint to stc"  
	x := x * aScale x.
	y := y * aScale y.
	^ self
    ].
    aScale isNumber ifTrue:[
	x := x * aScale.
	y := y * aScale.
	^ self
    ].

    "this is the general (& clean) code ..."

    scalePoint := aScale asPoint.
    x := x * scalePoint x.
    y := y * scalePoint y
!

translateBy:anOffset
    "translate the receiver, by replacing coordinates by the sum
     of the receivers coordinated and the scale (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."

    |offsetPoint|

    (anOffset isMemberOf:Point) ifTrue:[ "type hint to stc"   
	x := x + anOffset x.
	y := y + anOffset y.
	^ self
    ].
    anOffset isNumber ifTrue:[
	x := x + anOffset.
	y := y + anOffset.
	^ self
    ].

    "this is the general (& clean) code ..."

    offsetPoint := anOffset asPoint.
    x := x + anOffset x.
    y := y + anOffset y
! !

!Point methodsFor:'queries'!

isPoint
    "return true, if the receiver is some kind of point"

    ^ true
! !

!Point methodsFor:'misc'!

dist:aPoint 
    "return the distance between aPoint and the receiver."

    ^ (aPoint - self) r
!

dotProduct:aPoint 
    "return a number that is the dot product of the receiver and
     the argument, aPoint.  That is, the two points are
     multiplied and the coordinates of the result summed."

    |temp|

    temp := self * aPoint.
    ^ temp x abs + temp y abs
!

r
    "return the receiver's radius in a polar coordinate system.
     (i.e. the length of a vector from 0@0 to the receiver)"

    ^ (self dotProduct:self) sqrt

    "
     (1@1) r 
     (2@1) r 
     (2@0) r 
    "
!

angle 
    "return the receiver's angle in a polar coordinate system.
     (i.e. the angle of a vector from 0@0 to the receiver)"

    y < 0 ifTrue:[
	x < 0 ifTrue:[
	    ^  270 degreesToRadians - (y / x) arcTan
	].
	x = 0 ifTrue:[
	    ^ 180
	].
	^ 360 degreesToRadians - (y abs / x) arcTan
    ].
    x < 0 ifTrue:[
	^ 180 degreesToRadians - (y / x abs) arcTan 
    ].
    x = 0 ifTrue:[
	^ 0
    ].
    ^ (y / x) arcTan

    "
     (1@1) angle radiansToDegrees
     (2@1) angle radiansToDegrees   
    "
!

abs
    "return a new point with my coordinates taken from the absolute values."

    ^ (x abs) @ (y abs)
!

truncated
    "return a new point with my coordinates truncated as integer or the
     receiver, if already truncated."

    (x isInteger and:[y isInteger]) ifTrue:[^ self].
    ^ (x truncated) @ (y truncated)
!

rounded
    "return a new point with my coordinates rounded to the next integer
     coordinated (use for gridding) or the receiver of already rounded."

    (x isInteger and:[y isInteger]) ifTrue:[^ self].
    ^ (x rounded) @ (y rounded)
!

grid:gridPoint
    "return a new point with coordinates grided (i.e. rounded to the
     nearest point on the grid)"

    |newX newY gridX gridY|

    gridX := gridPoint x.
    (gridX <= 1) ifTrue:[
	newX := x asInteger
    ] ifFalse:[
	newX := ((x + (gridX // 2)) // gridX) * gridX
    ].
    gridY := gridPoint y.
    (gridY <= 1) ifTrue:[
	newY := y asInteger
    ] ifFalse:[
	newY := ((y + (gridY // 2)) // gridY) * gridY
    ].
    ^ newX @ newY
!

quadrantContaining:aPoint
    "return the number of the quadrant containing aPoint placing  
     the receiver at the origin, where the quadrants are numbered as  
     follows:
	   ^    2  |  3
	   Y    ------
		1  |  0

		X >
     This can be used for polygon operations (see Foley for examples).
    "

     aPoint x > x ifTrue:[
	 aPoint y >= y ifTrue:[^ 3].
	 ^ 0
     ].
     aPoint y >= y ifTrue: [^ 2].     
     ^ 1

     "
      (10 @ 10) quadrantContaining:(15 @ 15)
      (10 @ 10) quadrantContaining:(5 @ 5)    
      (10 @ 10) quadrantContaining:(5 @ 15)   
      (10 @ 10) quadrantContaining:(15 @ 5)  
     "
!

quadrant
    "return the number of the quadrant containing the receiver.
     quadrants are named as follows:

	   ^    2  |  3
	   Y    ------
		1  |  0

		X >
    "

    ^ 0@0 quadrantContaining:self
!

nearestIntegerPointOnLineFrom: point1 to: point2 
    "return the closest integer point to the receiver on the line 
     determined by (point1, point2)--much faster than the more 
     accurate version if the receiver and arguments are integer points.
     This method was found in the Manchester goody library."

    | dX dY newX newY dX2 dY2 intersect scale coeff |

    dX := point2 x - point1 x.
    dY := point2 y - point1 y.
    (dX = 0)ifTrue: [
	(dY = 0) ifTrue: [
	    intersect := point1
	] ifFalse: [
	    newX := point1 x.
	    scale := (y - point1 y) / dY.
	    newY := scale > 1 ifTrue: [
			point2 y
		    ] ifFalse: [
			scale < 0 ifTrue: [
			    point1 y
			] ifFalse: [
			    y
			]
		    ].

	    ^ (newX @ newY) rounded
	]
    ] ifFalse: [
	(dY = 0) ifTrue: [
	    intersect := x @ point1 y
	] ifFalse:[
	    dX2 := dX * dX.
	    dY2 := dY * dY.
	    coeff := ((dX * (y - point1 y)) - 
		     ((x - point1 x) * dY)) / (dX2 + dY2).
	    newX := x + (dY * coeff).
	    newY := y - (dX * coeff).
	    intersect := newX @ newY
	]
    ].

    scale := (intersect x - point1 x) / dX.

    ^ (scale > 1 ifTrue: [point2] ifFalse: [
      scale < 0 ifTrue: [point1] ifFalse: [intersect]]) rounded

    "
     120@40 nearestIntegerPointOnLineFrom: 30@120 to: 100@120 
     0@0 nearestIntegerPointOnLineFrom: 10@10 to: 100@100 
    "
! !

!Point methodsFor:'printing & storing'!

printOn:aStream
    "append a printed representation of the receiver to aStream"

    x printOn:aStream.
    aStream nextPut:$@.
    y printOn:aStream
!

storeOn:aStream
    "append my storeString to aStream"

    aStream nextPut:$(.
    x storeOn:aStream.
    aStream nextPut:$@.
    y storeOn:aStream.
    aStream nextPut:$)
! !