WindowingTransformation.st
changeset 72 3e84121988c3
parent 54 29a6b2f8e042
child 78 1c9c22df3251
--- a/WindowingTransformation.st	Mon Oct 10 03:30:48 1994 +0100
+++ b/WindowingTransformation.st	Mon Oct 10 03:34:45 1994 +0100
@@ -1,6 +1,6 @@
 "
  COPYRIGHT (c) 1992 by Claus Gittinger
-              All Rights Reserved
+	      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
@@ -10,25 +10,108 @@
  hereby transferred.
 "
 
-Object subclass: #WindowingTransformation
-        instanceVariableNames: 'scale translation'
-        classVariableNames: ''
-        poolDictionaries: ''
-        category: 'Graphics-Support'!
+'From Smalltalk/X, Version:2.10.3 on 20-sep-1994 at 0:15:56'!
+
+Object subclass:#WindowingTransformation
+	 instanceVariableNames:'scale translation'
+	 classVariableNames:''
+	 poolDictionaries:''
+	 category:'Graphics-Support'
+!
 
 WindowingTransformation comment:'
 COPYRIGHT (c) 1992 by Claus Gittinger
-              All Rights Reserved
+	      All Rights Reserved
 
-$Header: /cvs/stx/stx/libview/WindowingTransformation.st,v 1.5 1994-08-05 01:16:22 claus Exp $
+$Header: /cvs/stx/stx/libview/WindowingTransformation.st,v 1.6 1994-10-10 02:34:07 claus Exp $
 '!
 
-!WindowingTransformation class methodsFor: 'documentation'!
+!WindowingTransformation class methodsFor:'instance creation'!
+
+unit:unitSymbol on:device 
+    "returns a windowing transformation with scaling 
+     for unitSymbol and no translation (0@0).
+     With such a transformation, you can draw in your preferred 
+     units.
+     UnitSymbol may be #mm, #cm, #inch, #point, #twip or #pixel (default).
+     Twip is 1/20th of a point, point is 1/72th of an inch
+     (i.e. the print-unit which is also used for font sizes etc.) 
+     - not to confuse with device pixels."
+
+    |pixelPerUnitV pixelPerUnitH|
+
+    unitSymbol == #mm ifTrue:[
+	pixelPerUnitV := device verticalPixelPerMillimeter.
+	pixelPerUnitH := device horizontalPixelPerMillimeter 
+    ] ifFalse:[
+	unitSymbol == #cm ifTrue:[
+	    pixelPerUnitV := device verticalPixelPerMillimeter * 10.
+	    pixelPerUnitH := device horizontalPixelPerMillimeter * 10 
+	] ifFalse:[
+	    unitSymbol == #twip ifTrue:[
+		pixelPerUnitV := device verticalPixelPerInch / 1440.
+		pixelPerUnitH := device horizontalPixelPerInch / 1440 
+	    ] ifFalse:[
+		unitSymbol == #point ifTrue:[
+		    pixelPerUnitV := device verticalPixelPerInch / 72.
+		    pixelPerUnitH := device horizontalPixelPerInch / 72 
+		] ifFalse:[
+		    unitSymbol == #inch ifTrue:[
+			pixelPerUnitV := device verticalPixelPerInch.
+			pixelPerUnitH := device horizontalPixelPerInch 
+		    ] ifFalse:[
+			"sorry: unknown unit is taken as pixel"
+			^ self new scale:nil translation:(0 @ 0)
+		    ]
+		]
+	    ]
+	]
+    ].
+    ^ self new scale:(pixelPerUnitH @ pixelPerUnitV) translation:0
+!
+
+scale:aScale translation:aTranslation 
+    "returns a windowing transformation with a scale factor of  
+     aScale and a translation offset of aTranslation."
+
+    ^ self new scale:aScale translation:aTranslation
+!
+
+window:sourceRectangle viewport:destinationRectangle 
+    "returns a windowing transformation with a scale and
+     translation computed from sourceRectangle and destinationRectangle.
+     The scale and transformation are computed such that sourceRectangle
+     is transformed to destinationRectangle. Typically sourceRectangle
+     represents the logical coordinateSpace while destinationRectangle 
+     represents the device coordinateSpace."
+
+    |sX sY tX tY newScale|
+
+    sX := destinationRectangle width / sourceRectangle width.
+    sY := destinationRectangle height / sourceRectangle height.
+    tX := destinationRectangle left - sourceRectangle left.
+    tY := destinationRectangle top - sourceRectangle top.
+    ((sX = 1.0) and:[sY = 1.0]) ifTrue:[
+	newScale := 1 @ 1
+    ] ifFalse:[
+	newScale := sX @ sY
+    ].
+    ^ self new scale:newScale translation:(tX @ tY)
+!
+
+identity
+    "returns a windowing transformation with no scaling (nil) 
+     and no translation (0@0)."
+
+    ^ self new scale:1 translation:0
+! !
+
+!WindowingTransformation class methodsFor:'documentation'!
 
 copyright
 "
  COPYRIGHT (c) 1992 by Claus Gittinger
-              All Rights Reserved
+	      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
@@ -41,7 +124,7 @@
 
 version
 "
-$Header: /cvs/stx/stx/libview/WindowingTransformation.st,v 1.5 1994-08-05 01:16:22 claus Exp $
+$Header: /cvs/stx/stx/libview/WindowingTransformation.st,v 1.6 1994-10-10 02:34:07 claus Exp $
 "
 !
 
@@ -50,8 +133,8 @@
     I represent the ability to perform transformations in 2-D space.
 
     Instance variables are:
-        scale           <Number> or <Point> representing a linear scaling factor.
-        translation     <Number> or <Point> representing a translation in 2-D.
+	scale           <Number> or <Point> representing a linear scaling factor.
+	translation     <Number> or <Point> representing a translation in 2-D.
 
     All 2-D objects are supposed to be able to be transformed using
     instances of me.  Instances of me can also be combined to form a
@@ -59,67 +142,62 @@
 "
 ! !
 
-!WindowingTransformation methodsFor: 'accessing'!
-
-scale
-    "return a copy of the Point that represents the
-     current scale of the receiver."
+!WindowingTransformation methodsFor:'applying transform'!
 
-    scale == nil ifTrue:[
-        ^ Point x:1 y:1
+applyToX:aNumber
+    "Apply the receiver to a number representing an x-coordinate
+     and return the result."
+
+    scale isNil ifTrue:[
+	^ aNumber + translation x
     ].
-    ^ scale copy
-!
-
-scaleOfOne
-    "Set the scale of the receiver to the identity scale"
-
-    scale := nil
+    ^ (aNumber * scale x + translation x) asInteger
 !
 
-translation
-    "return a copy of the receiver's translation."
+applyToY:aNumber
+    "Apply the receiver to a number representing an y-coordinate
+     and return the result."
 
-    ^ translation copy
+    scale isNil ifTrue:[
+	^ aNumber + translation y
+    ].
+    ^ (aNumber * scale y + translation y) asInteger
 !
 
-translation: aValue
-    "Set the receiver's translation to aValue."
+applyScaleY:aNumber
+    "apply the scale only (if heights are to be transformed)"
 
-    translation := aValue
-! !
-
-!WindowingTransformation methodsFor: 'testing'!
+    scale isNil ifTrue:[^ aNumber].
+    ^ (aNumber * scale y) asInteger
+!
 
-noScale
-    "return true if the identity scale is in effect;
-         answer false, otherwise."
+applyScaleX:aNumber
+    "apply the scale only (if widths are to be transformed)"
 
-    ^ scale == nil
-! !
-
-!WindowingTransformation methodsFor: 'applying transform'!
+    scale isNil ifTrue:[^ aNumber].
+    ^ (aNumber * scale x) asInteger
+!
 
 applyInverseTo:anObject 
     "Apply the inverse of the receiver to anObject
-     and answer the result."
+     and return the result."
 
     |transformedObject|
 
     transformedObject := anObject translatedBy:(self inverseTranslation).
     scale == nil ifFalse:[
-        transformedObject scaleBy:(self inverseScale)
+	transformedObject scaleBy:(self inverseScale)
     ].
     ^ transformedObject
 !
 
 applyTo:anObject 
-    "Apply the receiver to anObject and answer the result."
+    "Apply the receiver to anObject and return the result."
 
     |transformedObject|
 
     scale == nil ifTrue:[
-        ^ anObject translateBy:translation.
+	^ anObject translateBy:translation.
     ].
     transformedObject := anObject scaledBy:scale
     transformedObject translateBy:translation.
@@ -138,26 +216,62 @@
 
     aTransformationScale := aTransformation scale.
     scale == nil ifTrue:[
-        aTransformation noScale ifTrue:[
-            newScale := nil
-        ] ifFalse:[
-            newScale := aTransformationScale
-        ].
-        newTranslation := translation + aTransformation translation
+	aTransformation noScale ifTrue:[
+	    newScale := nil
+	] ifFalse:[
+	    newScale := aTransformationScale
+	].
+	newTranslation := translation + aTransformation translation
     ] ifFalse:[
-        aTransformation noScale ifTrue:[
-            newScale := scale
-        ] ifFalse:[
-            newScale := scale * aTransformationScale
-        ].
-        newTranslation := translation
-                          + (scale * aTransformation translation)
+	aTransformation noScale ifTrue:[
+	    newScale := scale
+	] ifFalse:[
+	    newScale := scale * aTransformationScale
+	].
+	newTranslation := translation
+			  + (scale * aTransformation translation)
     ].
-    ^ WindowingTransformation scale:newScale
-                        translation:newTranslation
+    ^ (self class) 
+	  scale:newScale
+	  translation:newTranslation
 ! !
 
-!WindowingTransformation methodsFor: 'transforming'!
+!WindowingTransformation methodsFor:'transforming'!
+
+scaleBy:aScale 
+    "scale the receiver.
+     This is a destructive operation, modifying the transformation
+     represented by the receiver"
+
+    |newScale newTranslation|
+
+    aScale isNil ifTrue:[^ self].
+
+    scale isNil ifTrue:[
+	newScale := aScale asPoint
+    ] ifFalse:[
+	newScale := scale * aScale
+    ].
+    translation := translation * aScale.
+    scale := newScale.
+!
+
+translateBy:aTranslation 
+    "translate the receiver.
+     This is a destructive operation, modifying the transformation
+     represented by the receiver"
+
+    aTranslation isNil ifTrue:[^ self].
+
+    translation isNil ifTrue:[
+	translation := 0@0
+    ].
+    scale isNil ifTrue:[
+	translation := translation + aTranslation asPoint
+    ] ifFalse:[
+	translation := translation + (scale * aTranslation)
+    ].
+!
 
 scaledBy:aScale 
     "return a new WindowingTransformation with the scale and translation of 
@@ -166,19 +280,20 @@
     |checkedScale newScale newTranslation|
 
     aScale == nil ifTrue:[
-        newScale := scale.
-        newTranslation := translation
+	newScale := scale.
+	newTranslation := translation
     ] ifFalse:[
-        checkedScale := self checkScale:aScale.
-        scale == nil ifTrue:[
-            newScale := checkedScale
-        ] ifFalse:[
-            newScale := scale * checkedScale
-        ].
-        newTranslation := checkedScale * translation
+	checkedScale := self checkScale:aScale.
+	scale == nil ifTrue:[
+	    newScale := checkedScale
+	] ifFalse:[
+	    newScale := scale * checkedScale
+	].
+	newTranslation := checkedScale * translation
     ].
-    ^ WindowingTransformation scale:newScale
-                        translation:newTranslation
+    ^ (self class) 
+	  scale:newScale
+	  translation:newTranslation
 !
 
 translatedBy:aPoint 
@@ -186,18 +301,12 @@
      rotations as the receiver and with a translation of the current 
      translation plus aPoint."
 
-    ^ WindowingTransformation scale:scale
-                        translation:(translation + aPoint)
+    ^ (self class) 
+	  scale:scale
+	  translation:(translation + aPoint)
 ! !
 
-!WindowingTransformation methodsFor: 'printing'!
-
-printString
-    ^ (self class name, ' scale: ', scale printString,
-                  ' translation: ', translation printString)
-! !
-
-!WindowingTransformation methodsFor: 'private'!
+!WindowingTransformation methodsFor:'private'!
 
 checkScale:aScale
     "Converts aScale to the internal format of a floating-point Point."
@@ -206,7 +315,7 @@
 
     checkedScale := aScale asPoint.
     ^ Point x:checkedScale x asFloat
-            y:checkedScale y asFloat
+	    y:checkedScale y asFloat
 !
 
 inverseScale
@@ -217,7 +326,7 @@
 
     newScale := self checkScale:scale.
     ^ Point x:(1.0 / newScale x)
-            y:(1.0 / newScale y)
+	    y:(1.0 / newScale y)
 !
 
 inverseTranslation
@@ -228,47 +337,68 @@
 
     trans := translation asPoint.
     ^ Point x:trans x negated
-            y:trans y negated
+	    y:trans y negated
+! !
+
+!WindowingTransformation methodsFor:'accessing'!
+
+scale:aScale translation:aTranslation
+    "sets the scale to aScale and the translation to aTranslation."
+
+    scale := aScale asPoint.
+    translation := aTranslation asPoint
 !
 
-setScale:aScale translation:aTranslation
-    "Sets the scale to aScale and the translation to aTranslation."
-
-    scale := aScale.
-    translation := aTranslation
-! !
+translation:aValue
+    "Set the receiver's translation to aValue, a Point or Number."
 
-!WindowingTransformation class methodsFor: 'instance creation'!
+    translation := aValue asPoint
+!
 
-identity
-    "returns a windowing transformation with no scaling (nil) 
-     and no translation (0@0)."
+scale:aValue
+    "Set the receiver's scale to aValue, a Point or Number."
 
-    ^ self new setScale:nil translation:(Point x:0.0 y:0.0)
+    scale := aValue asPoint
 !
 
-scale:aScale translation:aTranslation 
-    "returns a windowing transformation with a scale factor of  
-     aScale and a translation offset of aTranslation."
+scale
+    "return a copy of the Point that represents the
+     current scale of the receiver."
 
-    ^ self new setScale:aScale translation:aTranslation
+    scale == nil ifTrue:[
+	^ Point x:1 y:1
+    ].
+    ^ scale copy
+!
+
+translation
+    "return a copy of the receiver's translation."
+
+    ^ translation copy
 !
 
-window:sourceRectangle viewport:destinationRectangle 
-    "returns a windowing transformation with a scale and
-     translation computed from sourceRectangle and destinationRectangle.
-     The scale and transformation are computed such that sourceRectangle
-     is transformed to destinationRectangle."
+scaleOfOne
+    "Set the scale of the receiver to the identity scale"
+
+    scale := nil
+! !
+
+!WindowingTransformation methodsFor:'testing'!
+
+noScale
+    "return true if the identity scale is in effect;
+     return false, otherwise."
 
-    |sX sY tX tY newScale|
-    sX := destinationRectangle width / sourceRectangle width.
-    sY := destinationRectangle height / sourceRectangle height.
-    tX := destinationRectangle left - sourceRectangle left.
-    tY := destinationRectangle top - sourceRectangle top.
-    ((sX = 1.0) and:[sY = 1.0]) ifTrue:[
-        newScale := nil
-    ] ifFalse:[
-        newScale := Point x:sX y:sY
-    ].
-    ^ self new setScale:newScale translation:(Point x:tX y:tY)
+    ^ scale == nil
 ! !
+
+!WindowingTransformation methodsFor:'printing'!
+
+printOn:aStream
+    aStream nextPutAll:self class name.
+    aStream nextPutAll:' scale: '.
+    scale printOn:aStream
+    aStream nextPutAll:' translation: '.
+    translation printOn:aStream
+! !
+