initial checkin
authorClaus Gittinger <cg@exept.de>
Thu, 07 Oct 1999 00:23:08 +0200
changeset 1250 76824ea90b46
parent 1249 a0e075238bb7
child 1251 2b4223c2e092
initial checkin
CompositeTransform.st
DisplayTransform.st
MatrixTransform2x3.st
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/CompositeTransform.st	Thu Oct 07 00:23:08 1999 +0200
@@ -0,0 +1,72 @@
+DisplayTransform subclass:#CompositeTransform
+	instanceVariableNames:'globalTransform localTransform'
+	classVariableNames:''
+	poolDictionaries:''
+	category:'Graphics-Transformations'
+!
+
+CompositeTransform comment:'A composite transform provides the effect of several levels of coordinate transformations.'!
+
+
+!CompositeTransform methodsFor:'accessing'!
+
+inverseTransformation
+	"Return the inverse transformation of the receiver"
+	^self species new
+		globalTransform: localTransform inverseTransformation
+		localTransform: globalTransform inverseTransformation! !
+
+!CompositeTransform methodsFor:'converting'!
+
+asCompositeTransform
+	^self!
+
+asMatrixTransform2x3
+	^globalTransform asMatrixTransform2x3
+		composedWithLocal: localTransform asMatrixTransform2x3! !
+
+!CompositeTransform methodsFor:'initialization'!
+
+globalTransform: gt localTransform: lt
+	globalTransform _ gt.
+	localTransform _ lt! !
+
+!CompositeTransform methodsFor:'testing'!
+
+isCompositeTransform
+	^true!
+
+isIdentity
+	^ globalTransform isIdentity and: [localTransform isIdentity]!
+
+isPureTranslation
+	^ globalTransform isPureTranslation and: [localTransform isPureTranslation]! !
+
+!CompositeTransform methodsFor:'transformations'!
+
+invert: aPoint
+	^ globalTransform invert: (localTransform invert: aPoint)!
+
+scale
+	^ localTransform scale * globalTransform scale!
+
+transform: aPoint
+	^ localTransform transform: (globalTransform transform: aPoint)! !
+
+!CompositeTransform methodsFor:'transforming points'!
+
+globalPointToLocal: aPoint
+	"Transform aPoint from global coordinates into local coordinates"
+	^localTransform globalPointToLocal:
+		(globalTransform globalPointToLocal: aPoint)!
+
+localPointToGlobal: aPoint
+	"Transform aPoint from global coordinates into local coordinates"
+	^globalTransform localPointToGlobal:
+		(localTransform localPointToGlobal: aPoint)! !
+
+!CompositeTransform class methodsFor:'documentation'!
+
+version
+    ^ '$Header: /cvs/stx/stx/libview2/CompositeTransform.st,v 1.1 1999-10-06 22:23:08 cg Exp $'
+! !
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/DisplayTransform.st	Thu Oct 07 00:23:08 1999 +0200
@@ -0,0 +1,146 @@
+Object subclass:#DisplayTransform
+	instanceVariableNames:''
+	classVariableNames:''
+	poolDictionaries:''
+	category:'Graphics-Transformations'
+!
+
+DisplayTransform comment:'This class represents a base for generic transformations of 2D points between different coordinate systems (including scaling and rotation). The transformations map objects between one coordinate system and another where it is assumed that a nested hierarchy of transformations can be defined.
+
+It is assumed that transformations deal with Integer points. All transformations should return Integer coordinates (even though float points may be passed in as argument).
+
+Compositions of transformations MUST work in the following order. A ''global'' transformation (the argument in #composedWithGlobal:) is defined as a transformation that takes place between the receiver (the ''local'') transformation and any ''global'' point computations, whereas a ''local'' transformation (e.g., the argument in #composedWithLocal:) takes place between the receiver (''global'') and any ''local'' points. For the transformation methods this means that combining a global and a local transformation will result in the following order:
+
+		globalPointToLocal: globalPoint
+			"globalPoint -> globalTransform -> localTransform -> locaPoint"
+			^localTransform globalPointToLocal:
+				(globalTransform globalPointToLocal: globalPoint)
+
+		localPointToGlobal: localPoint
+			"localPoint -> localTransform -> globalTransform -> globalPoint"
+			^globalTransform localPointToGlobal:
+				(localTransform localPointToGlobal: localPoint)
+
+'!
+
+
+!DisplayTransform class methodsFor:'instance creation'!
+
+identity
+	^self new setIdentity! !
+
+!DisplayTransform methodsFor:'accessing'!
+
+inverseTransformation
+	"Return the inverse transformation of the receiver"
+	^self subclassResponsibility! !
+
+!DisplayTransform methodsFor:'composing'!
+
+composedWithGlobal: aTransformation
+	"Return the composition of the receiver and the global transformation passed in.
+	A 'global' transformation is defined as a transformation that takes place
+	between the receiver (the 'local') transformation and any 'global' point
+	computations, e.g., for the methods
+
+		globalPointToLocal: globalPoint
+			globalPoint -> globalTransform -> localTransform -> locaPoint
+
+		localPointToGlobal: localPoint
+			localPoint -> localTransform -> globalTransform -> globalPoint
+
+		"
+	^aTransformation composedWithLocal: self!
+
+composedWithLocal: aTransformation
+	"Return the composition of the receiver and the local transformation passed in.
+	A 'local' transformation is defined as a transformation that takes place
+	between the receiver (the 'global') transformation and any 'local' point
+	computations, e.g., for the methods
+
+		globalPointToLocal: globalPoint
+			globalPoint -> globalTransform -> localTransform -> locaPoint
+
+		localPointToGlobal: localPoint
+			localPoint -> localTransform -> globalTransform -> globalPoint
+
+		"
+	self isIdentity ifTrue:[^ aTransformation].
+	aTransformation isIdentity ifTrue:[^ self].
+	^ CompositeTransform new globalTransform: self
+							localTransform: aTransformation! !
+
+!DisplayTransform methodsFor:'converting'!
+
+asCompositeTransform
+	"Represent the receiver as a composite transformation"
+	^CompositeTransform new
+		globalTransform: self
+		localTransform: self species identity!
+
+asMatrixTransform2x3
+	"Represent the receiver as a 2x3 matrix transformation"
+	^self subclassResponsibility! !
+
+!DisplayTransform methodsFor:'initialize'!
+
+setIdentity
+	"Initialize the receiver to the identity transformation (e.g., not affecting points)"
+	^self subclassResponsibility! !
+
+!DisplayTransform methodsFor:'testing'!
+
+isCompositeTransform
+	"Return true if the receiver is a composite transformation.
+	Composite transformations may have impact on the accuracy."
+	^false!
+
+isIdentity
+	"Return true if the receiver is the identity transform; that is, if applying to a point returns the point itself."
+	^self subclassResponsibility!
+
+isMatrixTransform2x3
+	"Return true if the receiver is 2x3 matrix transformation"
+	^false!
+
+isMorphicTransform
+	"Return true if the receiver is a MorphicTransform, that is specifies the transformation values explicitly."
+	^false!
+
+isPureTranslation
+	"Return true if the receiver specifies no rotation or scaling."
+	^self subclassResponsibility! !
+
+!DisplayTransform methodsFor:'transforming points'!
+
+globalPointToLocal: aPoint
+	"Transform aPoint from global coordinates into local coordinates"
+	^self subclassResponsibility!
+
+globalPointsToLocal: inArray
+	"Transform all the points of inArray from global into local coordinates"
+	^inArray collect:[:pt| self globalPointToLocal: pt]!
+
+localPointToGlobal: aPoint
+	"Transform aPoint from local coordinates into global coordinates"
+	^self subclassResponsibility!
+
+localPointsToGlobal: inArray
+	"Transform all the points of inArray from local into global coordinates"
+	^inArray collect:[:pt| self localPointToGlobal: pt]! !
+
+!DisplayTransform methodsFor:'transforming rects'!
+
+globalBoundsToLocal: aRectangle
+	"Transform aRectangle from global coordinates into local coordinates"
+	^Rectangle encompassing: (self globalPointsToLocal: aRectangle corners)!
+
+localBoundsToGlobal: aRectangle
+	"Transform aRectangle from local coordinates into global coordinates"
+	^Rectangle encompassing: (self localPointsToGlobal: aRectangle corners)! !
+
+!DisplayTransform class methodsFor:'documentation'!
+
+version
+    ^ '$Header: /cvs/stx/stx/libview2/DisplayTransform.st,v 1.1 1999-10-06 22:22:58 cg Exp $'
+! !
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/MatrixTransform2x3.st	Thu Oct 07 00:23:08 1999 +0200
@@ -0,0 +1,285 @@
+DisplayTransform variableWordSubclass:#MatrixTransform2x3
+	instanceVariableNames:''
+	classVariableNames:''
+	poolDictionaries:''
+	category:'Graphics-Transformations'
+!
+
+MatrixTransform2x3 comment:'This class represents a transformation for points, that is a combination of scale, offset, and rotation. It is implemented as a 2x3 matrix containing the transformation from the local coordinate system in the global coordinate system. Thus, transforming points from local to global coordinates is fast and cheap whereas transformations from global to local coordinate systems are relatively expensive.
+
+Implementation Note: It is assumed that the transformation deals with Integer points. All transformations will return Integer coordinates (even though float points may be passed in here).'!
+
+
+!MatrixTransform2x3 class methodsFor:'instance creation'!
+
+identity
+	^self new setScale: 1.0!
+
+new
+	^self new: 6!
+
+transformFromLocal: localBounds toGlobal: globalBounds
+	^((self withOffset: (globalBounds center)) composedWithLocal:
+		(self withScale: (globalBounds extent / localBounds extent) asFloatPoint))
+			composedWithLocal: (self withOffset: localBounds center negated)
+"
+	^(self identity)
+		setScale: (globalBounds extent / localBounds extent) asFloatPoint;
+		setOffset: localBounds center negated asFloatPoint;
+		composedWithGlobal:(self withOffset: globalBounds center asFloatPoint)
+"!
+
+withAngle: angle
+	^self new setAngle: angle!
+
+withOffset: aPoint
+	^self identity setOffset: aPoint!
+
+withRotation: angle
+	^self new setAngle: angle!
+
+withScale: aPoint
+	^self new setScale: aPoint! !
+
+!MatrixTransform2x3 methodsFor:'accessing'!
+
+at: index
+	<primitive: 'primitiveFloatArrayAt'>
+	^Float fromIEEE32Bit: (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!
+
+inverseTransformation
+	"Return the inverse transformation of the receiver.
+	The inverse transformation is computed by first calculating
+	the inverse offset and then computing transformations
+	for the two identity vectors (1@0) and (0@1)"
+	| r1 r2 r3 m |
+	r3 _ self invertPoint: 0@0.
+	r1 _ (self invertPoint: 1@0) - r3.
+	r2 _ (self invertPoint: 0@1) - r3.
+	m _ self species new.
+	m
+		a11: r1 x; a12: r2 x; a13: r3 x;
+		a21: r1 y; a22: r2 y; a23: r3 y.
+	^m!
+
+offset
+	^self a13 @ self a23!
+
+offset: aPoint
+	self a13: aPoint x asFloat.
+	self a23: aPoint y asFloat.! !
+
+!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!
+
+hash
+	| result |
+	<primitive:'primitiveFloatArrayHash'>
+	result _ 0.
+	1 to: self size do:[:i| result _ result + (self basicAt: i) ].
+	^result bitAnd: 16r1FFFFFFF! !
+
+!MatrixTransform2x3 methodsFor:'composing'!
+
+composedWithLocal: aTransformation
+	"Return the composition of the receiver and the local transformation passed in"
+	aTransformation isMatrixTransform2x3 ifFalse:[^super composedWith: aTransformation].
+	^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! !
+
+!MatrixTransform2x3 methodsFor:'converting'!
+
+asMatrixTransform2x3
+	^self! !
+
+!MatrixTransform2x3 methodsFor:'element access'!
+
+a11
+	^self at: 1!
+
+a11: value
+	 self at: 1 put: value!
+
+a12
+	^self at: 2!
+
+a12: value
+	 self at: 2 put: value!
+
+a13
+	^self at: 3!
+
+a13: value
+	 self at: 3 put: value!
+
+a21
+	 ^self at: 4!
+
+a21: value
+	 self at: 4 put: value!
+
+a22
+	 ^self at: 5!
+
+a22: value
+	 self at: 5 put: value!
+
+a23
+	 ^self at: 6!
+
+a23: value
+	 self at: 6 put: value! !
+
+!MatrixTransform2x3 methodsFor:'initialize'!
+
+setIdentiy
+	"Initialize the receiver to the identity transformation (e.g., not affecting points)"
+	self
+		a11: 1.0; a12: 0.0; a13: 0.0;
+		a21: 0.0; a22: 1.0; a23: 0.0.! !
+
+!MatrixTransform2x3 methodsFor:'printing'!
+
+printOn: aStream
+	aStream 
+		nextPutAll: self class name;
+		nextPut: $(;
+		cr; print: self a11; tab; print: self a12; tab; print: self a13;
+		cr; print: self a21; tab; print: self a22; tab; print: self a23;
+		cr; nextPut:$).! !
+
+!MatrixTransform2x3 methodsFor:'private'!
+
+setAngle: angle
+	"Set the raw rotation angle in the receiver"
+	| rad s c |
+	rad := angle degreesToRadians.
+	s := rad sin.
+	c := rad cos.
+	self a11: c.
+	self a12: s negated.
+	self a21: s.
+	self a22: c.!
+
+setOffset: aPoint
+	"Set the raw offset in the receiver"
+	| pt |
+	pt _ aPoint asPoint.
+	self a13: pt x asFloat.
+	self a23: pt y asFloat.!
+
+setScale: aPoint
+	"Set the raw scale in the receiver"
+	| pt |
+	pt _ aPoint asPoint.
+	self a11: pt x asFloat.
+	self a22: pt y asFloat.! !
+
+!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]]!
+
+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]]]! !
+
+!MatrixTransform2x3 methodsFor:'transforming points'!
+
+globalPointToLocal: aPoint
+	"Transform aPoint from global coordinates into local coordinates"
+	<primitive: 'm23PrimitiveInvertPoint'>
+	^(self invertPoint: aPoint) rounded!
+
+invertPoint: aPoint
+	"Transform aPoint from global coordinates into local coordinates"
+	| x y det a11 a12 a21 a22 detX detY |
+	x _ aPoint x asFloat - (self a13).
+	y _ aPoint y asFloat - (self a23).
+	a11 _ self a11.	a12 _ self a12.
+	a21 _ self a21.	a22 _ self a22.
+	det _ (a11 * a22) - (a12 * a21).
+	det = 0.0 ifTrue:[^0@0]. "So we have at least a valid result"
+	det _ 1.0 / det.
+	detX _ (x * a22) - (a12 * y).
+	detY _ (a11 * y) - (x * a21).
+	^(detX * det) @ (detY * det)!
+
+localPointToGlobal: aPoint
+	"Transform aPoint from local coordinates into global coordinates"
+	<primitive: 'm23PrimitiveTransformPoint'>
+	^(self transformPoint: aPoint) rounded!
+
+transformPoint: aPoint
+	"Transform aPoint from local coordinates into global coordinates"
+	| x y |
+	x _ (aPoint x * self a11) + (aPoint y * self a12) + self a13.
+	y _ (aPoint x * self a21) + (aPoint y * self a22) + self a23.
+	^x @ y! !
+
+!MatrixTransform2x3 methodsFor:'transforming rects'!
+
+globalBounds: srcRect toLocal: dstRect
+	"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!
+
+localBoundsToGlobal: aRectangle
+	"Transform aRectangle from local coordinates into global coordinates"
+	^self localBounds: aRectangle toGlobal: Rectangle new! !
+
+!MatrixTransform2x3 class methodsFor:'documentation'!
+
+version
+    ^ '$Header: /cvs/stx/stx/libview2/MatrixTransform2x3.st,v 1.1 1999-10-06 22:22:49 cg Exp $'
+! !