WindowingTransformation.st
author claus
Wed, 03 May 1995 17:43:56 +0200
changeset 137 523edf3204e4
parent 81 4ba554473294
child 219 9ff0660f447f
permissions -rw-r--r--
.

"
 COPYRIGHT (c) 1992 by Claus Gittinger
	      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
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 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 comment:'
COPYRIGHT (c) 1992 by Claus Gittinger
	      All Rights Reserved

$Header: /cvs/stx/stx/libview/WindowingTransformation.st,v 1.9 1995-05-03 15:43:45 claus Exp $
'!

!WindowingTransformation class methodsFor:'documentation '!

copyright
"
 COPYRIGHT (c) 1992 by Claus Gittinger
	      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
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"
!

version
"
$Header: /cvs/stx/stx/libview/WindowingTransformation.st,v 1.9 1995-05-03 15:43:45 claus Exp $
"
!

documentation
"
    instances of WindowingTransformation can be used to scale, translate or
    generally transform other objects in 2D space. 
    They can also be set as the translation in a graphic context, 
    which will then apply this to all of its drawing operations 
    (see GraphicContext>>transformation:).

    All 2-D objects are supposed to be able to be transformed using
    instances of me.  Multiple instances of me can also be combined to form a
    single composite transformation.

    Instance variables are:
	scale           <Number> or <Point> representing a linear scaling factor.
			nil is interpreted as 1@1

	translation     <Number> or <Point> representing a translation in 2-D.
			nil is interpreted as 0@0

"
!

examples
"
    example (drawing in inches):

     |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 


    example (drawing in millimeters):

     |v|

     v := View new realize.
     (Delay forSeconds:3) wait.
     v transformation:(WindowingTransformation unit:#mm on:Display).
     'now, we can think of drawing in millimeters ...'.
     v displayLineFrom:5@5 to:20@5 


    example (drawing magnified):

     |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 


    example (drawing shrunk):

     |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 

"
! !

!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: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 
    "
!

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 
    "
!

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 
    "
!

identity
    "returns a windowing transformation with no scaling (1@1) 
     and no translation (0@0)."

    ^ self basicNew scale:nil translation:nil 
! !

!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)"

    scale isNil ifTrue:[^ aNumber].
    ^ aNumber / scale x
!

applyInverseScaleY:aNumber
    "apply the scale only (if heights are to be transformed)"

    scale isNil ifTrue:[^ aNumber].
    ^ aNumber / scale y
!

applyInverseTo:anObject 
    "Apply the inverse of the receiver to anObject
     and return the result. This can be used to map back from logical
     to physical coordinates, for example."

    |transformedObject|

    translation isNil ifTrue:[
	scale isNil ifTrue:[
	    ^ anObject
	].
	^ anObject scaledBy:self inverseScale 
    ].
    transformedObject := anObject translatedBy:(self inverseTranslation).
    scale notNil ifTrue:[
	transformedObject scaleBy:(self inverseScale).
    ].
    ^ transformedObject
!

transformPoint:p 
    "Apply the receiver to a point.
     This is destructive in that the point is being modified,
     not a copy."

    scale isNil ifTrue:[
	translation isNil ifTrue:[
	    ^ p
	].
	^ p + translation
    ].
    translation isNil ifTrue:[
	^ p * scale
    ].
    ^ (p * scale + translation)
!

compose:aTransformation 
    "return a new WindowingTransformation that is the
     composition of the receiver and aTransformation.
     The effect of applying the resulting WindowingTransformation
     to an object is the same as that of first applying
     aTransformation to the object and then applying the 
     receiver to its result."

    |aTransformationScale newScale newTranslation|

    aTransformationScale := aTransformation scale.
    scale isNil ifTrue:[
	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)
    ].
    ^ (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|

    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
!

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)
! !

!WindowingTransformation methodsFor:'private'!

checkScale:aScale
    "Converts aScale to the internal format of a floating-point Point."

    |checkedScale|

    checkedScale := aScale asPoint.
    ^ Point x:checkedScale x asFloat
	    y:checkedScale y asFloat
!

inverseScale
    "return with a Point representing the inverse of my
     scale."

    |newScale|

    newScale := self checkScale:scale.
    ^ Point x:(1.0 / newScale x)
	    y:(1.0 / newScale y)
!

inverseTranslation
    "return with a Point representing the inverse of my
     translation."

    |trans|

    trans := translation asPoint.
    ^ Point x:trans x negated
	    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
    "return true if the identity scale is in effect;
     return false, otherwise."

    ^ scale == nil
! !

!WindowingTransformation methodsFor:'printing'!

printOn:aStream
    aStream nextPutAll:self class name.
    aStream nextPutAll:' scale: '.
    scale printOn:aStream.
    aStream nextPutAll:' translation: '.
    translation printOn:aStream
! !