DisplayTransform.st
author Claus Gittinger <cg@exept.de>
Tue, 23 Apr 2019 16:30:55 +0200
changeset 8674 e29a561c0fbe
parent 8384 c473ce4aa06a
permissions -rw-r--r--
#FEATURE by cg class: SimpleView added: #isDialogBox

"{ Encoding: utf8 }"

"
 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.
"
"{ Package: 'stx:libview' }"

"{ NameSpace: Smalltalk }"

Object subclass:#DisplayTransform
	instanceVariableNames:''
	classVariableNames:''
	poolDictionaries:''
	category:'Graphics-Transformations'
!

DisplayTransform comment:'This class represents a base for generic transformations of 2D points between different coordinate systems (including scaling and rotation). The transformations map objects between one coordinate system and another where it is assumed that a nested hierarchy of transformations can be defined.

It is assumed that transformations deal with Integer points. All transformations should return Integer coordinates (even though float points may be passed in as argument).

Compositions of transformations MUST work in the following order. A ''global'' transformation (the argument in #composedWithGlobal:) is defined as a transformation that takes place between the receiver (the ''local'') transformation and any ''global'' point computations, whereas a ''local'' transformation (e.g., the argument in #composedWithLocal:) takes place between the receiver (''global'') and any ''local'' points. For the transformation methods this means that combining a global and a local transformation will result in the following order:

		globalPointToLocal: globalPoint
			"globalPoint -> globalTransform -> localTransform -> locaPoint"
			^localTransform globalPointToLocal:
				(globalTransform globalPointToLocal: globalPoint)

		localPointToGlobal: localPoint
			"localPoint -> localTransform -> globalTransform -> globalPoint"
			^globalTransform localPointToGlobal:
				(localTransform localPointToGlobal: localPoint)

'
!

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

!DisplayTransform class methodsFor:'instance creation'!

identity
	^self new setIdentity
! !

!DisplayTransform class methodsFor:'queries'!

isAbstract
    "Return if this class is an abstract class.
     True is returned here for myself only; false for subclasses.
     Abstract subclasses must redefine this again."

    ^ self == DisplayTransform.
! !

!DisplayTransform methodsFor:'accessing'!

inverseTransformation
	"Return the inverse transformation of the receiver"
	^self subclassResponsibility
! !

!DisplayTransform methodsFor:'composing'!

composedWithGlobal: aTransformation
	"Return the composition of the receiver and the global transformation passed in.
	A 'global' transformation is defined as a transformation that takes place
	between the receiver (the 'local') transformation and any 'global' point
	computations, e.g., for the methods

		globalPointToLocal: globalPoint
			globalPoint -> globalTransform -> localTransform -> locaPoint

		localPointToGlobal: localPoint
			localPoint -> localTransform -> globalTransform -> globalPoint

		"
	^aTransformation composedWithLocal: self
!

composedWithLocal: aTransformation
        "Return the composition of the receiver and the local transformation passed in.
        A 'local' transformation is defined as a transformation that takes place
        between the receiver (the 'global') transformation and any 'local' point
        computations, e.g., for the methods

                globalPointToLocal: globalPoint
                        globalPoint -> globalTransform -> localTransform -> locaPoint

                localPointToGlobal: localPoint
                        localPoint -> localTransform -> globalTransform -> globalPoint

                "
        self isIdentityTransformation ifTrue:[^ aTransformation].
        aTransformation isIdentityTransformation ifTrue:[^ self].
        ^ CompositeTransform new 
                globalTransform: self
                localTransform: aTransformation

    "Modified: / 14-06-2018 / 10:31:37 / Claus Gittinger"
! !

!DisplayTransform methodsFor:'converting'!

asCompositeTransform
    "Represent the receiver as a composite transformation"

    ^CompositeTransform new
            globalTransform: self
            localTransform: self species identity

    "Modified: / 14-06-2018 / 10:31:50 / Claus Gittinger"
!

asMatrixTransform2x3
	"Represent the receiver as a 2x3 matrix transformation"
	^self subclassResponsibility
! !

!DisplayTransform methodsFor:'initialize'!

setIdentity
    "Initialize the receiver to the identity transformation (e.g., not affecting points)"

    ^self subclassResponsibility
! !

!DisplayTransform methodsFor:'testing'!

isCompositeTransform
	"Return true if the receiver is a composite transformation.
	Composite transformations may have impact on the accuracy."
	^false
!

isIdentityTransformation
    "Return true if the receiver is the identity transform; that is, if applying to a point returns the point itself."

    ^ self subclassResponsibility
!

isMatrixTransform2x3
	"Return true if the receiver is 2x3 matrix transformation"
	^false
!

isMorphicTransform
	"Return true if the receiver is a MorphicTransform, that is specifies the transformation values explicitly."
	^false
!

isNoScale
    "return true if the identity scale is in effect (i.e. saleFactor is 1);
     return false, otherwise."

    ^ self subclassResponsibility
!

noScale
    "return true if the identity scale is in effect (i.e. saleFactor is 1);
     return false, otherwise.
     Obsolete: use isNoScale"

    <resource: #obsolete>

    ^ self isNoScale
! !

!DisplayTransform methodsFor:'transforming points'!

applyInverseTo:aPoint
    self subclassResponsibility
    "/ ^ self invertPoint: aPoint

    "Modified: / 14-06-2018 / 10:29:56 / Claus Gittinger"
!

applyScaleX:aNumber
    self subclassResponsibility
    "/ ^ (self transformPoint: aNumber @ 0) x

    "Modified: / 14-06-2018 / 10:30:11 / Claus Gittinger"
!

applyScaleY:aNumber
    self subclassResponsibility
    "/ ^ (self transformPoint: 0 @ aNumber) y

    "Modified: / 14-06-2018 / 10:30:17 / Claus Gittinger"
!

applyTo:aPoint
    self subclassResponsibility
    "/ ^ self transformPoint: aPoint

    "Modified: / 14-06-2018 / 10:30:24 / Claus Gittinger"
!

globalPointToLocal: aPoint
	"Transform aPoint from global coordinates into local coordinates"
	^self subclassResponsibility
!

globalPointsToLocal: inArray
	"Transform all the points of inArray from global into local coordinates"
	^inArray collect:[:pt| self globalPointToLocal: pt]
!

localPointToGlobal: aPoint
	"Transform aPoint from local coordinates into global coordinates"
	^self subclassResponsibility
!

localPointsToGlobal: inArray
	"Transform all the points of inArray from local into global coordinates"
	^inArray collect:[:pt| self localPointToGlobal: pt]
! !

!DisplayTransform methodsFor:'transforming rects'!

globalBoundsToLocal: aRectangle
	"Transform aRectangle from global coordinates into local coordinates"
	^Rectangle encompassing: (self globalPointsToLocal: aRectangle corners)
!

localBoundsToGlobal: aRectangle
	"Transform aRectangle from local coordinates into global coordinates"
	^Rectangle encompassing: (self localPointsToGlobal: aRectangle corners)
! !

!DisplayTransform class methodsFor:'documentation'!

version
    ^ '$Header$'
!

version_CVS
    ^ '$Header$'
! !