WindowingTransformation.st
changeset 601 2c4c1e797909
parent 219 9ff0660f447f
child 611 e0442439a3c6
--- a/WindowingTransformation.st	Tue Apr 23 22:06:00 1996 +0200
+++ b/WindowingTransformation.st	Tue Apr 23 22:12:21 1996 +0200
@@ -10,15 +10,139 @@
  hereby transferred.
 "
 
-'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 class methodsFor:'instance creation'!
+
+identity
+    "returns a windowing transformation with no scaling (1@1) 
+     and no translation (0@0)."
+
+    ^ self basicNew scale:nil translation:nil 
+!
+
+scale:aScale translation:aTranslation 
+    "returns a windowing transformation with a scale factor of  
+     aScale and a translation offset of aTranslation."
+
+    ^ self basicNew scale:aScale translation:aTranslation
+
+    "
+     |v|
+
+     v := View new realize.
+     (Delay forSeconds:3) wait.
+     v transformation:(WindowingTransformation scale:2 translation:0).
+     'now, everything is magnfied by 2'.
+     v displayLineFrom:10@10 to:30@30 
+    "
+    "
+     |v|
+
+     v := View new realize.
+     (Delay forSeconds:3) wait.
+     v transformation:(WindowingTransformation scale:0.5 translation:0).
+     'now, everything is shrunk by 2'.
+     v displayLineFrom:10@10 to:30@30 
+    "
+!
+
+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|
 
-Object subclass:#WindowingTransformation
-	 instanceVariableNames:'scale translation'
-	 classVariableNames:''
-	 poolDictionaries:''
-	 category:'Graphics-Support'
+    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:nil
+		    ]
+		]
+	    ]
+	]
+    ].
+    ^ self basicNew scale:(pixelPerUnitH @ pixelPerUnitV) translation:nil
+
+    "
+     |v|
+
+     v := View new realize.
+     (Delay forSeconds:3) wait.
+     v transformation:(WindowingTransformation unit:#inch on:Display).
+     'now, we can think of drawing in inches ...'.
+     v displayLineFrom:0.5@0.5 to:1@1 
+    "
 !
 
+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 newTranslation|
+
+    sX := destinationRectangle width / sourceRectangle width.
+    sY := destinationRectangle height / sourceRectangle height.
+    tX := destinationRectangle left - sourceRectangle left.
+    tY := destinationRectangle top - sourceRectangle top.
+    ((tX = 1.0) and:[tY = 1.0]) ifTrue:[
+	newTranslation := nil
+    ] ifFalse:[
+	newTranslation := tX @ tY
+    ].
+    ((sX = 1.0) and:[sY = 1.0]) ifTrue:[
+	newScale := nil
+    ] ifFalse:[
+	newScale := sX @ sY
+    ].
+    ^ self basicNew scale:newScale translation:newTranslation
+
+    "
+     |v|
+
+     v := View new realize.
+     (Delay forSeconds:3) wait.
+     v transformation:(WindowingTransformation 
+				window:(0@0 corner:1@1)
+				viewport:(0@0 corner:100@100)).
+     'now, we can think of drawing in 0..1/0..1 coordinates'.
+     v displayLineFrom:0.1@0.1 to:0.9@0.9 
+    "
+! !
+
 !WindowingTransformation class methodsFor:'documentation '!
 
 copyright
@@ -35,10 +159,6 @@
 "
 !
 
-version
-    ^ '$Header: /cvs/stx/stx/libview/WindowingTransformation.st,v 1.10 1995-11-11 15:53:42 cg Exp $'
-!
-
 documentation
 "
     instances of WindowingTransformation can be used to scale, translate or
@@ -107,212 +227,72 @@
      v displayLineFrom:10@10 to:30@30 
 
 "
+!
+
+version
+    ^ '$Header: /cvs/stx/stx/libview/WindowingTransformation.st,v 1.11 1996-04-23 20:10:42 cg Exp $'
 ! !
 
-!WindowingTransformation class methodsFor:'instance creation'!
+!WindowingTransformation methodsFor:'accessing'!
+
+scale
+    "return a copy of the Point that represents the
+     current scale of the receiver."
 
-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."
+    scale isNil ifTrue:[^ (1@1) copy].
+    ^ scale copy
+!
 
-    |pixelPerUnitV pixelPerUnitH|
+scale:aScale
+    "Set the receiver's scale to aScale, a Point or Number."
 
-    unitSymbol == #mm ifTrue:[
-	pixelPerUnitV := device verticalPixelPerMillimeter.
-	pixelPerUnitH := device horizontalPixelPerMillimeter 
+    aScale isNil ifTrue:[
+	scale := aScale
     ] 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:nil
-		    ]
-		]
-	    ]
-	]
+	scale := aScale asPoint.
     ].
-    ^ self basicNew scale:(pixelPerUnitH @ pixelPerUnitV) translation:nil
-
-    "
-     |v|
-
-     v := View new realize.
-     (Delay forSeconds:3) wait.
-     v transformation:(WindowingTransformation unit:#inch on:Display).
-     'now, we can think of drawing in inches ...'.
-     v displayLineFrom:0.5@0.5 to:1@1 
-    "
 !
 
-scale:aScale translation:aTranslation 
-    "returns a windowing transformation with a scale factor of  
-     aScale and a translation offset of aTranslation."
-
-    ^ self basicNew scale:aScale translation:aTranslation
-
-    "
-     |v|
+scale:aScale translation:aTranslation
+    "sets the scale to aScale and the translation to aTranslation."
 
-     v := View new realize.
-     (Delay forSeconds:3) wait.
-     v transformation:(WindowingTransformation scale:2 translation:0).
-     'now, everything is magnfied by 2'.
-     v displayLineFrom:10@10 to:30@30 
-    "
-    "
-     |v|
-
-     v := View new realize.
-     (Delay forSeconds:3) wait.
-     v transformation:(WindowingTransformation scale:0.5 translation:0).
-     'now, everything is shrunk by 2'.
-     v displayLineFrom:10@10 to:30@30 
-    "
+    aScale isNil ifTrue:[
+	scale := aScale
+    ] ifFalse:[
+	scale := aScale asPoint.
+    ].
+    aTranslation isNil ifTrue:[
+	translation := aTranslation
+    ] ifFalse:[
+	translation := aTranslation asPoint
+    ]
 !
 
-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 newTranslation|
+scaleOfOne
+    "Set the scale of the receiver to the identity scale"
 
-    sX := destinationRectangle width / sourceRectangle width.
-    sY := destinationRectangle height / sourceRectangle height.
-    tX := destinationRectangle left - sourceRectangle left.
-    tY := destinationRectangle top - sourceRectangle top.
-    ((tX = 1.0) and:[tY = 1.0]) ifTrue:[
-	newTranslation := nil
-    ] ifFalse:[
-	newTranslation := tX @ tY
-    ].
-    ((sX = 1.0) and:[sY = 1.0]) ifTrue:[
-	newScale := nil
-    ] ifFalse:[
-	newScale := sX @ sY
-    ].
-    ^ self basicNew scale:newScale translation:newTranslation
-
-    "
-     |v|
-
-     v := View new realize.
-     (Delay forSeconds:3) wait.
-     v transformation:(WindowingTransformation 
-				window:(0@0 corner:1@1)
-				viewport:(0@0 corner:100@100)).
-     'now, we can think of drawing in 0..1/0..1 coordinates'.
-     v displayLineFrom:0.1@0.1 to:0.9@0.9 
-    "
+    scale := nil
 !
 
-identity
-    "returns a windowing transformation with no scaling (1@1) 
-     and no translation (0@0)."
+translation
+    "return a copy of the receiver's translation."
+
+    translation isNil ifTrue:[^ (0@0) copy].
+    ^ translation copy
+!
 
-    ^ self basicNew scale:nil translation:nil 
+translation:aTranslation
+    "Set the receiver's translation to aTranslation, a Point or Number."
+
+    aTranslation isNil ifTrue:[
+	translation := aTranslation
+    ] ifFalse:[
+	translation := aTranslation asPoint
+    ]
 ! !
 
 !WindowingTransformation methodsFor:'applying transform'!
 
-applyToX:aNumber
-    "Apply the receiver to a number representing an x-coordinate
-     and return the result."
-
-    |t s|
-
-    scale isNil ifTrue:[s := 1] ifFalse:[s := scale x].
-    translation isNil ifTrue:[t := 0] ifFalse:[t := translation x].
-    ^ aNumber * s + t
-!
-
-applyToY:aNumber
-    "Apply the receiver to a number representing an y-coordinate
-     and return the result."
-
-    |t s|
-
-    scale isNil ifTrue:[s := 1] ifFalse:[s := scale y].
-    translation isNil ifTrue:[t := 0] ifFalse:[t := translation y].
-    ^ aNumber * s + t
-!
-
-applyScaleX:aNumber
-    "apply the scale only (if widths are to be transformed)"
-
-    scale isNil ifTrue:[^ aNumber].
-    ^ aNumber * scale x
-!
-
-applyScaleY:aNumber
-    "apply the scale only (if heights are to be transformed)"
-
-    scale isNil ifTrue:[^ aNumber].
-    ^ aNumber * scale y
-!
-
-applyTo:anObject 
-    "Apply the receiver to anObject and return the result."
-
-    |transformedObject|
-
-    scale isNil ifTrue:[
-	translation isNil ifTrue:[
-	    ^ anObject
-	].
-	^ anObject translatedBy:translation 
-    ].
-    transformedObject := anObject scaledBy:scale.
-    translation notNil ifTrue:[
-	transformedObject translateBy:translation.
-    ].
-    ^ transformedObject
-!
-
-applyInverseToX:aNumber
-    "Apply the receiver to a number representing an x-coordinate
-     and return the result."
-
-    |t s|
-
-    scale isNil ifTrue:[s := 1] ifFalse:[s := scale x].
-    translation isNil ifTrue:[t := 0] ifFalse:[t := translation x].
-    ^ (aNumber - t) / s
-!
-
-applyInverseToY:aNumber
-    "Apply the receiver to a number representing an y-coordinate
-     and return the result."
-
-    |t s|
-
-    scale isNil ifTrue:[s := 1] ifFalse:[s := scale y].
-    translation isNil ifTrue:[t := 0] ifFalse:[t := translation y].
-    ^ (aNumber - t) / s
-!
-
 applyInverseScaleX:aNumber
     "apply the scale only (if widths are to be transformed)"
 
@@ -347,21 +327,80 @@
     ^ transformedObject
 !
 
-transformPoint:p 
-    "Apply the receiver to a point.
-     This is destructive in that the point is being modified,
-     not a copy."
+applyInverseToX:aNumber
+    "Apply the receiver to a number representing an x-coordinate
+     and return the result."
+
+    |t s|
+
+    scale isNil ifTrue:[s := 1] ifFalse:[s := scale x].
+    translation isNil ifTrue:[t := 0] ifFalse:[t := translation x].
+    ^ (aNumber - t) / s
+!
+
+applyInverseToY:aNumber
+    "Apply the receiver to a number representing an y-coordinate
+     and return the result."
+
+    |t s|
+
+    scale isNil ifTrue:[s := 1] ifFalse:[s := scale y].
+    translation isNil ifTrue:[t := 0] ifFalse:[t := translation y].
+    ^ (aNumber - t) / s
+!
+
+applyScaleX:aNumber
+    "apply the scale only (if widths are to be transformed)"
+
+    scale isNil ifTrue:[^ aNumber].
+    ^ aNumber * scale x
+!
+
+applyScaleY:aNumber
+    "apply the scale only (if heights are to be transformed)"
+
+    scale isNil ifTrue:[^ aNumber].
+    ^ aNumber * scale y
+!
+
+applyTo:anObject 
+    "Apply the receiver to anObject and return the result."
+
+    |transformedObject|
 
     scale isNil ifTrue:[
 	translation isNil ifTrue:[
-	    ^ p
+	    ^ anObject
 	].
-	^ p + translation
+	^ anObject translatedBy:translation 
+    ].
+    transformedObject := anObject scaledBy:scale.
+    translation notNil ifTrue:[
+	transformedObject translateBy:translation.
     ].
-    translation isNil ifTrue:[
-	^ p * scale
-    ].
-    ^ (p * scale + translation)
+    ^ transformedObject
+!
+
+applyToX:aNumber
+    "Apply the receiver to a number representing an x-coordinate
+     and return the result."
+
+    |t s|
+
+    scale isNil ifTrue:[s := 1] ifFalse:[s := scale x].
+    translation isNil ifTrue:[t := 0] ifFalse:[t := translation x].
+    ^ aNumber * s + t
+!
+
+applyToY:aNumber
+    "Apply the receiver to a number representing an y-coordinate
+     and return the result."
+
+    |t s|
+
+    scale isNil ifTrue:[s := 1] ifFalse:[s := scale y].
+    translation isNil ifTrue:[t := 0] ifFalse:[t := translation y].
+    ^ aNumber * s + t
 !
 
 compose:aTransformation 
@@ -394,80 +433,33 @@
     ^ (self class) 
 	  scale:newScale
 	  translation:newTranslation
-! !
-
-!WindowingTransformation methodsFor:'transforming'!
-
-scaleBy:aScale 
-    "scale the receiver.
-     This is a destructive operation, modifying the transformation
-     represented by the receiver"
-
-    |newScale|
-
-    aScale isNil ifTrue:[^ self].
-
-    scale isNil ifTrue:[
-	newScale := aScale asPoint
-    ] ifFalse:[
-	newScale := scale * aScale
-    ].
-    translation notNil ifTrue:[
-	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 
-     the receiver both scaled by aScale."
-
-    |checkedScale newScale newTranslation|
+transformPoint:p 
+    "Apply the receiver to a point.
+     This is destructive in that the point is being modified,
+     not a copy."
 
-    aScale isNil ifTrue:[
-	newScale := scale.
-	newTranslation := translation
-    ] ifFalse:[
-	checkedScale := self checkScale:aScale.
-	scale isNil ifTrue:[
-	    newScale := checkedScale
-	] ifFalse:[
-	    newScale := scale * checkedScale
+    scale isNil ifTrue:[
+	translation isNil ifTrue:[
+	    ^ p
 	].
-	translation notNil ifTrue:[
-	    newTranslation := checkedScale * translation
-	]
+	^ p + translation
+    ].
+    translation isNil ifTrue:[
+	^ p * scale
     ].
-    ^ (self class) 
-	  scale:newScale
-	  translation:newTranslation
-!
+    ^ (p * scale + translation)
+! !
+
+!WindowingTransformation methodsFor:'printing'!
 
-translatedBy:aPoint 
-    "return a new WindowingTransformation with the same scale and 
-     rotations as the receiver and with a translation of the current 
-     translation plus aPoint."
-
-    ^ (self class) 
-	  scale:scale
-	  translation:(translation + aPoint)
+printOn:aStream
+    aStream nextPutAll:self class name.
+    aStream nextPutAll:' scale: '.
+    scale printOn:aStream.
+    aStream nextPutAll:' translation: '.
+    translation printOn:aStream
 ! !
 
 !WindowingTransformation methodsFor:'private'!
@@ -504,64 +496,6 @@
 	    y:trans y negated
 ! !
 
-!WindowingTransformation methodsFor:'accessing'!
-
-scale:aScale translation:aTranslation
-    "sets the scale to aScale and the translation to aTranslation."
-
-    aScale isNil ifTrue:[
-	scale := aScale
-    ] ifFalse:[
-	scale := aScale asPoint.
-    ].
-    aTranslation isNil ifTrue:[
-	translation := aTranslation
-    ] ifFalse:[
-	translation := aTranslation asPoint
-    ]
-!
-
-translation:aTranslation
-    "Set the receiver's translation to aTranslation, a Point or Number."
-
-    aTranslation isNil ifTrue:[
-	translation := aTranslation
-    ] ifFalse:[
-	translation := aTranslation asPoint
-    ]
-!
-
-scale:aScale
-    "Set the receiver's scale to aScale, a Point or Number."
-
-    aScale isNil ifTrue:[
-	scale := aScale
-    ] ifFalse:[
-	scale := aScale asPoint.
-    ].
-!
-
-scale
-    "return a copy of the Point that represents the
-     current scale of the receiver."
-
-    scale isNil ifTrue:[^ (1@1) copy].
-    ^ scale copy
-!
-
-translation
-    "return a copy of the receiver's translation."
-
-    translation isNil ifTrue:[^ (0@0) copy].
-    ^ translation copy
-!
-
-scaleOfOne
-    "Set the scale of the receiver to the identity scale"
-
-    scale := nil
-! !
-
 !WindowingTransformation methodsFor:'testing'!
 
 noScale
@@ -571,13 +505,77 @@
     ^ scale == nil
 ! !
 
-!WindowingTransformation methodsFor:'printing'!
+!WindowingTransformation methodsFor:'transforming'!
+
+scaleBy:aScale 
+    "scale the receiver.
+     This is a destructive operation, modifying the transformation
+     represented by the receiver"
+
+    |newScale|
+
+    aScale isNil ifTrue:[^ self].
+
+    scale isNil ifTrue:[
+	newScale := aScale asPoint
+    ] ifFalse:[
+	newScale := scale * aScale
+    ].
+    translation notNil ifTrue:[
+	translation := translation * aScale.
+    ].
+    scale := newScale.
+!
+
+scaledBy:aScale 
+    "return a new WindowingTransformation with the scale and translation of 
+     the receiver both scaled by aScale."
+
+    |checkedScale newScale newTranslation|
 
-printOn:aStream
-    aStream nextPutAll:self class name.
-    aStream nextPutAll:' scale: '.
-    scale printOn:aStream.
-    aStream nextPutAll:' translation: '.
-    translation printOn:aStream
+    aScale isNil ifTrue:[
+	newScale := scale.
+	newTranslation := translation
+    ] ifFalse:[
+	checkedScale := self checkScale:aScale.
+	scale isNil ifTrue:[
+	    newScale := checkedScale
+	] ifFalse:[
+	    newScale := scale * checkedScale
+	].
+	translation notNil ifTrue:[
+	    newTranslation := checkedScale * translation
+	]
+    ].
+    ^ (self class) 
+	  scale:newScale
+	  translation:newTranslation
+!
+
+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)
+    ].
+!
+
+translatedBy:aPoint 
+    "return a new WindowingTransformation with the same scale and 
+     rotations as the receiver and with a translation of the current 
+     translation plus aPoint."
+
+    ^ (self class) 
+	  scale:scale
+	  translation:(translation + aPoint)
 ! !