WindowingTransformation.st
author claus
Mon, 10 Oct 1994 03:34:45 +0100
changeset 72 3e84121988c3
parent 54 29a6b2f8e042
child 78 1c9c22df3251
permissions -rw-r--r--
*** empty log message ***

"
 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.6 1994-10-10 02:34:07 claus Exp $
'!

!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

 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.6 1994-10-10 02:34:07 claus Exp $
"
!

documentation
"
    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.

    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
    single composite transformation.
"
! !

!WindowingTransformation methodsFor:'applying transform'!

applyToX:aNumber
    "Apply the receiver to a number representing an x-coordinate
     and return the result."

    scale isNil ifTrue:[
	^ aNumber + translation x
    ].
    ^ (aNumber * scale x + translation x) asInteger
!

applyToY:aNumber
    "Apply the receiver to a number representing an y-coordinate
     and return the result."

    scale isNil ifTrue:[
	^ aNumber + translation y
    ].
    ^ (aNumber * scale y + translation y) asInteger
!

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

    scale isNil ifTrue:[^ aNumber].
    ^ (aNumber * scale y) asInteger
!

applyScaleX:aNumber
    "apply the scale only (if widths are to be transformed)"

    scale isNil ifTrue:[^ aNumber].
    ^ (aNumber * scale x) asInteger
!

applyInverseTo:anObject 
    "Apply the inverse of the receiver to anObject
     and return the result."

    |transformedObject|

    transformedObject := anObject translatedBy:(self inverseTranslation).
    scale == nil ifFalse:[
	transformedObject scaleBy:(self inverseScale)
    ].
    ^ transformedObject
!

applyTo:anObject 
    "Apply the receiver to anObject and return the result."

    |transformedObject|

    scale == nil ifTrue:[
	^ anObject translateBy:translation.
    ].
    transformedObject := anObject scaledBy:scale
    transformedObject translateBy:translation.
    ^ transformedObject
!

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 == nil 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 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 
     the receiver both scaled by aScale."

    |checkedScale newScale newTranslation|

    aScale == nil ifTrue:[
	newScale := scale.
	newTranslation := translation
    ] ifFalse:[
	checkedScale := self checkScale:aScale.
	scale == nil ifTrue:[
	    newScale := checkedScale
	] ifFalse:[
	    newScale := scale * checkedScale
	].
	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."

    scale := aScale asPoint.
    translation := aTranslation asPoint
!

translation:aValue
    "Set the receiver's translation to aValue, a Point or Number."

    translation := aValue asPoint
!

scale:aValue
    "Set the receiver's scale to aValue, a Point or Number."

    scale := aValue asPoint
!

scale
    "return a copy of the Point that represents the
     current scale of the receiver."

    scale == nil ifTrue:[
	^ Point x:1 y:1
    ].
    ^ scale copy
!

translation
    "return a copy of the receiver's translation."

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