home *** CD-ROM | disk | FTP | other *** search
/ Il CD di internet / CD.iso / SOURCE / OOP / _SMALTAL.TAR / usr / lib / smalltalk / contrib / Point.st next >
Encoding:
Text File  |  1990-05-23  |  3.4 KB  |  198 lines

  1. "=====================================================================
  2. |    Point Class Definitions
  3.  =====================================================================
  4.  
  5. By Doug McCallum <uunet!ico.isc.com!dougm>
  6. Additions by uunet!nfsun!nfstar!sbyrne (Steve Byrne)
  7. "
  8.  
  9. "
  10. |     Change Log
  11. | ============================================================================
  12. | Author       Date       Change 
  13. | dougm         25 Apr 90      Some cleanup plus merged changes by sbyrne
  14. |
  15. | dougm         16 Apr 90      Created basic Point class.
  16. |
  17. "
  18.  
  19. Object subclass: #Point
  20.        instanceVariableNames: 'x y'
  21.        classVariableNames: ''
  22.        poolDictionaries: ''
  23.        category: nil !
  24.  
  25. Point comment:
  26. 'Beginning of a Point class for simple display manipulation.  Has not been
  27.  exhaustively tested but appears to work for the basic primitives and for
  28.  the needs of the Rectangle class.' !
  29.  
  30. "move to Number ??? "
  31. "VVVVVVVVVVVVVVVVVVVVVVVVVVVVVVVVVVVVVVVVVV"
  32. !Number methodsFor: 'point creation'!
  33.  
  34. @ y
  35.     ^Point x: self y: y
  36. !
  37.  
  38. asPoint
  39.     ^Point x: self y: self
  40. !!
  41. "^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^"
  42.  
  43. !Point class methodsFor: 'instance creation'!
  44.  
  45. x: xInteger y: yInteger
  46.     ^self new x: xInteger y: yInteger    
  47. !!
  48.  
  49. !Point methodsFor: 'printing'!
  50.  
  51. printOn: aStream
  52.     x printOn: aStream.
  53.     '@' printOn: aStream.
  54.     y printOn: aStream
  55. !!
  56.  
  57. !Point methodsFor: 'storing'!
  58.  
  59. storeOn: aStream
  60.     x storeOn: aStream.
  61.     '@' storeOn: aStream.
  62.     y storeOn: aStream
  63. !!
  64.  
  65. !Point methodsFor: 'accessing'!
  66.  
  67. x
  68.     ^x
  69. !
  70.  
  71. y
  72.     ^y
  73. !
  74.  
  75. x: aNumber
  76.     x _ aNumber
  77. !
  78.  
  79. y: aNumber
  80.     y _ aNumber
  81. !
  82.  
  83. x: anXNumber y: aYNumber
  84.     x _ anXNumber.
  85.     y _ aYNumber
  86. !
  87.  
  88. asPoint
  89.     ^self            "But I already am a point!"
  90. !!
  91.  
  92. !Point methodsFor: 'arithmetic'!
  93.  
  94. + delta
  95.     | deltapt |
  96.     deltapt _ delta asPoint.
  97.     ^Point x: x + deltapt x y: y + deltapt y
  98. !
  99.  
  100. - delta
  101.     | deltapt |
  102.     deltapt _ delta asPoint.
  103.     ^Point x: x - deltapt x y: y - deltapt y
  104. !
  105.  
  106. * scale
  107.     |deltapt|
  108.     deltapt _ scale asPoint.
  109.     ^Point x: (x * deltapt x) y: (y * deltapt y)
  110. !
  111.  
  112. / scale
  113.     | deltapt |
  114.     deltapt _ scale asPoint.
  115.     ^Point x: (x / deltapt x) y: (y / deltapt y)
  116. !
  117.  
  118. // scale
  119.     | deltapt |
  120.     deltapt _ scale asPoint.
  121.     ^Point x: (x // deltapt x) y: (y // deltapt y)
  122. !
  123.  
  124. abs
  125.     ^Point x: (x abs) y: (y abs)
  126. !!
  127.  
  128. !Point methodsFor: 'truncation and round off'!
  129. rounded
  130.     ^Point x: (x rounded) y: (y rounded)
  131. !
  132.  
  133. truncateTo: grid
  134.     ^Point x: ((x // grid) * grid) y: (y // grid) * grid
  135. !!
  136.  
  137. !Point methodsFor: 'comparing'!
  138.  
  139. < aPoint
  140.     ^(x < (aPoint x)) and: [ (y < (aPoint y)) ]
  141. !
  142.  
  143. > aPoint
  144.     ^(x > (aPoint x)) and: [ (y > (aPoint y)) ]
  145. !
  146.  
  147. <= aPoint
  148.     ^(self > aPoint) not    "unverified"
  149. !
  150.  
  151. >= aPoint
  152.     ^(self < aPoint) not    "unverified"
  153. !
  154.  
  155. max: aPoint
  156.     (self>aPoint)
  157.     ifTrue: [^self]
  158.     ifFalse:[^aPoint]
  159. !
  160.  
  161. min: aPoint
  162.     (self<aPoint)
  163.     ifTrue: [^self]
  164.     ifFalse:[^aPoint]
  165. !!    
  166.  
  167. !Point methodsFor: 'point functions'!
  168.  
  169. dist: aPoint
  170.     | a b |
  171.     a _ x - (aPoint x).
  172.     b _ y - (aPoint y).
  173.     ^((a squared)+(b squared)) sqrt
  174. !
  175.  
  176. dotProduct: aPoint
  177.     ^(x * aPoint x) + (y * aPoint y)
  178. !
  179.  
  180. grid: aPoint
  181.     ^Point x: (x roundTo: (aPoint x)) y: (y roundTo: (aPoint y))
  182. !
  183.  
  184. normal
  185. "rotate the Point 90degrees clockwise and get the unit vector"
  186.     |len|
  187.     len _ ((x squared) + (y squared)) sqrt.
  188.     ^Point x: ((y asFloat negated)/len) y: (x/len)
  189. !
  190.  
  191. transpose
  192.     ^Point x: y y: x
  193. !
  194.  
  195. truncatedGrid: aPoint
  196.     ^Point x: (x truncateTo: (aPoint x)) y: (y truncateTo: (aPoint y))
  197. !!
  198.