WindowingTransformation.st
author claus
Fri, 03 Jun 1994 02:54:39 +0200
changeset 46 7b331e9012fd
parent 5 e5942fea6925
child 54 29a6b2f8e042
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.
"

Object subclass: #WindowingTransformation
        instanceVariableNames: 'scale translation'
        classVariableNames: ''
        poolDictionaries: ''
        category: 'Graphics-Support'!

WindowingTransformation comment:'
COPYRIGHT (c) 1992 by Claus Gittinger
              All Rights Reserved
'!

!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.4 1994-06-03 00:54:06 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: 'accessing'!

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
!

scaleOfOne
    "Set the scale of the receiver to the identity scale"

    scale := nil
!

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

    ^ translation copy
!

translation: aValue
    "Set the receiver's translation to aValue."

    translation := aValue
! !

!WindowingTransformation methodsFor: 'testing'!

noScale
    "return true if the identity scale is in effect;
         answer false, otherwise."

    ^ scale == nil
! !

!WindowingTransformation methodsFor: 'applying transform'!

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

    |transformedObject|

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

applyTo:anObject 
    "Apply the receiver to anObject and answer 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)
    ].
    ^ WindowingTransformation scale:newScale
                        translation:newTranslation
! !

!WindowingTransformation methodsFor: 'transforming'!

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
    ].
    ^ WindowingTransformation 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."

    ^ WindowingTransformation scale:scale
                        translation:(translation + aPoint)
! !

!WindowingTransformation methodsFor: 'printing'!

printString
    ^ (self class name, ' scale: ', scale printString,
                  ' translation: ', translation printString)
! !

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

setScale:aScale translation:aTranslation
    "Sets the scale to aScale and the translation to aTranslation."

    scale := aScale.
    translation := aTranslation
! !

!WindowingTransformation class methodsFor: 'instance creation'!

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

    ^ self new setScale:nil translation:(Point x:0.0 y:0.0)
!

scale:aScale translation:aTranslation 
    "returns a windowing transformation with a scale factor of  
     aScale and a translation offset of aTranslation."

    ^ self new setScale: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."

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