*** empty log message ***
authorClaus Gittinger <cg@exept.de>
Tue, 18 Jul 2000 14:21:06 +0200
changeset 1380 a999c793cd59
parent 1379 fc637aed5a94
child 1381 1035403e302e
*** empty log message ***
MatrixTransform2x3.st
--- a/MatrixTransform2x3.st	Tue Jul 18 13:22:06 2000 +0200
+++ b/MatrixTransform2x3.st	Tue Jul 18 14:21:06 2000 +0200
@@ -1,4 +1,6 @@
-DisplayTransform variableWordSubclass:#MatrixTransform2x3
+"{ Package: 'stx:libview2' }"
+
+DisplayTransform variableFloatSubclass:#MatrixTransform2x3
 	instanceVariableNames:''
 	classVariableNames:''
 	poolDictionaries:''
@@ -44,15 +46,19 @@
 !MatrixTransform2x3 methodsFor:'accessing'!
 
 at: index
-	<primitive: 'primitiveFloatArrayAt'>
-	^Float fromIEEE32Bit: (self basicAt: index)!
+"/        <primitive: 'primitiveFloatArrayAt'>
+"/        ^Float fromIEEE32Bit: (self basicAt: index)
+          ^ self basicAt: index
+!
 
 at: index put: value
-	<primitive: 'primitiveFloatArrayAtPut'>
-	value isFloat 
-		ifTrue:[self basicAt: index put: value asIEEE32BitWord]
-		ifFalse:[self at: index put: value asFloat].
-	^value!
+"/        <primitive: 'primitiveFloatArrayAtPut'>
+"/        value isFloat 
+"/                ifTrue:[self basicAt: index put: value asIEEE32BitWord]
+"/                ifFalse:[self at: index put: value asFloat].
+"/        ^value
+        ^ self basicAt: index put:value
+!
 
 inverseTransformation
 	"Return the inverse transformation of the receiver.
@@ -79,20 +85,25 @@
 !MatrixTransform2x3 methodsFor:'comparing'!
 
 = MatrixTransform2x3
-	| length |
-	<primitive:'primitiveFloatArrayEqual'>
-	self class = MatrixTransform2x3 class ifFalse:[^false].
-	length _ self size.
-	(length = MatrixTransform2x3 size) ifFalse:[^false].
-	1 to: self size do:[:i| (self at: i) = (MatrixTransform2x3 at: i) ifFalse:[^false]].
-	^true!
+        | length |
+"/        <primitive:'primitiveFloatArrayEqual'>
+        self class = MatrixTransform2x3 class ifFalse:[^false].
+        length _ self size.
+        (length = MatrixTransform2x3 size) ifFalse:[^false].
+        1 to: self size do:[:i| (self at: i) = (MatrixTransform2x3 at: i) ifFalse:[^false]].
+        ^true
+!
 
 hash
-	| result |
-	<primitive:'primitiveFloatArrayHash'>
-	result _ 0.
-	1 to: self size do:[:i| result _ result + (self basicAt: i) ].
-	^result bitAnd: 16r1FFFFFFF! !
+        | result |
+"/        <primitive:'primitiveFloatArrayHash'>
+"/        result _ 0.
+"/        1 to: self size do:[:i| result _ result + (self basicAt: i) ].
+"/        ^result bitAnd: 16r1FFFFFFF
+        result _ 0.
+        1 to: self size do:[:i| result _ result + (self basicAt: i) hash ].
+        ^result bitAnd: 16r1FFFFFFF
+! !
 
 !MatrixTransform2x3 methodsFor:'composing'!
 
@@ -102,24 +113,25 @@
 	^self composedWithLocal: aTransformation asMatrixTransform2x3 into: self class new!
 
 composedWithLocal: aTransformation into: result
-	"Return the composition of the receiver and the local transformation passed in.
-	Store the composed matrix into result."
-	| a11 a12 a13 a21 a22 a23 b11 b12 b13 b21 b22 b23 matrix |
-	<primitive: 'm23PrimitiveComposeMatrix'>
-	matrix _ aTransformation asMatrixTransform2x3.
-	a11 _ self a11.		b11 _ matrix a11.
-	a12 _ self a12.		b12 _ matrix a12.
-	a13 _ self a13.		b13 _ matrix a13.
-	a21 _ self a21.		b21 _ matrix a21.
-	a22 _ self a22.		b22 _ matrix a22.
-	a23 _ self a23.		b23 _ matrix a23.
-	result a11: (a11 * b11) + (a12 * b21).
-	result a12: (a11 * b12) + (a12 * b22).
-	result a13: a13 + (a11 * b13) + (a12 * b23).
-	result a21: (a21 * b11) + (a22 * b21).
-	result a22: (a21 * b12) + (a22 * b22).
-	result a23: a23 + (a21 * b13) + (a22 * b23).
-	^result! !
+        "Return the composition of the receiver and the local transformation passed in.
+        Store the composed matrix into result."
+        | a11 a12 a13 a21 a22 a23 b11 b12 b13 b21 b22 b23 matrix |
+"/        <primitive: 'm23PrimitiveComposeMatrix'>
+        matrix _ aTransformation asMatrixTransform2x3.
+        a11 _ self a11.                 b11 _ matrix a11.
+        a12 _ self a12.                 b12 _ matrix a12.
+        a13 _ self a13.                 b13 _ matrix a13.
+        a21 _ self a21.                 b21 _ matrix a21.
+        a22 _ self a22.                 b22 _ matrix a22.
+        a23 _ self a23.                 b23 _ matrix a23.
+        result a11: (a11 * b11) + (a12 * b21).
+        result a12: (a11 * b12) + (a12 * b22).
+        result a13: a13 + (a11 * b13) + (a12 * b23).
+        result a21: (a21 * b11) + (a22 * b21).
+        result a22: (a21 * b12) + (a22 * b22).
+        result a23: a23 + (a21 * b13) + (a22 * b23).
+        ^result
+! !
 
 !MatrixTransform2x3 methodsFor:'converting'!
 
@@ -212,25 +224,28 @@
 !MatrixTransform2x3 methodsFor:'testing'!
 
 isIdentity
-	"Return true if the receiver is the identity transform; that is, if applying to a point returns the point itself."
-	<primitive: 'm23PrimitiveIsIdentity'>
-	^self isPureTranslation and:[self a13 = 0.0 and:[self a23 = 0.0]]!
+        "Return true if the receiver is the identity transform; that is, if applying to a point returns the point itself."
+"/        <primitive: 'm23PrimitiveIsIdentity'>
+        ^self isPureTranslation and:[self a13 = 0.0 and:[self a23 = 0.0]]
+!
 
 isMatrixTransform2x3
 	"Return true if the receiver is 2x3 matrix transformation"
 	^true!
 
 isPureTranslation
-	"Return true if the receiver specifies no rotation or scaling."
-	<primitive: 'm23PrimitiveIsPureTranslation'>
-	^self a11 = 1.0 and:[self a12 = 0.0 and:[self a22 = 0.0 and:[self a21 = 1.0]]]! !
+        "Return true if the receiver specifies no rotation or scaling."
+"/        <primitive: 'm23PrimitiveIsPureTranslation'>
+        ^self a11 = 1.0 and:[self a12 = 0.0 and:[self a22 = 0.0 and:[self a21 = 1.0]]]
+! !
 
 !MatrixTransform2x3 methodsFor:'transforming points'!
 
 globalPointToLocal: aPoint
-	"Transform aPoint from global coordinates into local coordinates"
-	<primitive: 'm23PrimitiveInvertPoint'>
-	^(self invertPoint: aPoint) rounded!
+        "Transform aPoint from global coordinates into local coordinates"
+"/        <primitive: 'm23PrimitiveInvertPoint'>
+        ^(self invertPoint: aPoint) rounded
+!
 
 invertPoint: aPoint
 	"Transform aPoint from global coordinates into local coordinates"
@@ -247,9 +262,10 @@
 	^(detX * det) @ (detY * det)!
 
 localPointToGlobal: aPoint
-	"Transform aPoint from local coordinates into global coordinates"
-	<primitive: 'm23PrimitiveTransformPoint'>
-	^(self transformPoint: aPoint) rounded!
+        "Transform aPoint from local coordinates into global coordinates"
+"/        <primitive: 'm23PrimitiveTransformPoint'>
+        ^(self transformPoint: aPoint) rounded
+!
 
 transformPoint: aPoint
 	"Transform aPoint from local coordinates into global coordinates"
@@ -261,18 +277,20 @@
 !MatrixTransform2x3 methodsFor:'transforming rects'!
 
 globalBounds: srcRect toLocal: dstRect
-	"Transform aRectangle from global coordinates into local coordinates"
-	<primitive:'m23PrimitiveInvertRectInto'>
-	^super globalBoundsToLocal: srcRect!
+        "Transform aRectangle from global coordinates into local coordinates"
+"/        <primitive:'m23PrimitiveInvertRectInto'>
+        ^super globalBoundsToLocal: srcRect
+!
 
 globalBoundsToLocal: aRectangle
 	"Transform aRectangle from global coordinates into local coordinates"
 	^self globalBounds: aRectangle toLocal: Rectangle new!
 
 localBounds: srcRect toGlobal: dstRect
-	"Transform aRectangle from local coordinates into global coordinates"
-	<primitive:'m23PrimitiveTransformRectInto'>
-	^super localBoundsToGlobal: srcRect!
+        "Transform aRectangle from local coordinates into global coordinates"
+"/        <primitive:'m23PrimitiveTransformRectInto'>
+        ^super localBoundsToGlobal: srcRect
+!
 
 localBoundsToGlobal: aRectangle
 	"Transform aRectangle from local coordinates into global coordinates"
@@ -281,5 +299,5 @@
 !MatrixTransform2x3 class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libview2/MatrixTransform2x3.st,v 1.1 1999-10-06 22:22:49 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libview2/MatrixTransform2x3.st,v 1.2 2000-07-18 12:21:06 cg Exp $'
 ! !