1"======================================================================
2|
3|   Compositional transformation classes using CairoMatrix
4|
5|
6 ======================================================================"
7
8
9"======================================================================
10|
11| Copyright 2008 Free Software Foundation, Inc.
12| Written by Tony Garnock-Jones and Michael Bridgen.
13|
14| This file is part of the GNU Smalltalk class library.
15|
16| The GNU Smalltalk class library is free software; you can redistribute it
17| and/or modify it under the terms of the GNU Lesser General Public License
18| as published by the Free Software Foundation; either version 2.1, or (at
19| your option) any later version.
20|
21| The GNU Smalltalk class library is distributed in the hope that it will be
22| useful, but WITHOUT ANY WARRANTY; without even the implied warranty of
23| MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU Lesser
24| General Public License for more details.
25|
26| You should have received a copy of the GNU Lesser General Public License
27| along with the GNU Smalltalk class library; see the file COPYING.LIB.
28| If not, write to the Free Software Foundation, 59 Temple Place - Suite
29| 330, Boston, MA 02110-1301, USA.
30|
31 ======================================================================"
32
33CStruct subclass: CairoMatrix [
34    <declaration: #(
35      (#xx #double)
36      (#yx #double)
37      (#xy #double)
38      (#yy #double)
39      (#x0 #double)
40      (#y0 #double))>
41
42    <category: 'Cairo-C interface'>
43
44    initIdentity [
45	<category: 'initialize'>
46        Cairo matrixInitIdentity: self.
47    ]
48
49    withPoint: aPoint do: block [
50	<category: 'using'>
51	^block
52	    value: self
53	    value: (CDouble gcValue: aPoint x)
54	    value: (CDouble gcValue: aPoint y)
55    ]
56
57    copy [
58	<category: 'copying'>
59        | shiny |
60        shiny := CairoMatrix gcNew.
61        Cairo matrixInit: shiny
62	      xx: self xx value
63	      yx: self yx value
64	      xy: self xy value
65	      yy: self yy value
66	      x0: self x0 value
67	      y0: self y0 value.
68        ^ shiny
69    ]
70]
71
72
73Object subclass: TransformVisitor [
74    rotateBy: rads [
75	"Visitor method for rotation by aPoint."
76
77	<category: 'visiting'>
78	self subclassResponsibility
79    ]
80
81    scaleBy: aPoint [
82	"Visitor method for scaling by aPoint."
83
84	<category: 'visiting'>
85	self subclassResponsibility
86    ]
87
88    transformByMatrix: aMatrixTransform [
89	"Visitor method for transforms by an arbitrary matrix."
90
91	<category: 'visiting'>
92	self subclassResponsibility
93    ]
94
95    translateBy: aPoint [
96	"Visitor method for translations by aPoint."
97
98	<category: 'visiting'>
99	self subclassResponsibility
100    ]
101
102]
103
104Object subclass: Transform [
105    | matrix |
106
107    <category: 'Cairo-Transformation matrices'>
108    <comment: 'A note on transforms: to be compositional, the most
109straight-forward thing is to always use a transformation matrix.  However,
110a lot of the time, we''ll be doing just one kind of transformation;
111e.g., a scale, or a translation.  Further, we may only ever modify a
112transformation in one way, like translating a translation.  For this
113reason, we specialise for each of the translations and provide a generic
114matrix implementation for composing heterogeneous transformations.'>
115
116    Transform class >> new [
117	"Return an instance of the receiver representing the identity
118	 transform."
119
120	<category: 'instance creation'>
121	^ super new initialize
122    ]
123
124    Transform class >> identity [
125        "Return the identity transform, that leaves its visitor
126        unchanged."
127
128	<category: 'instance creation'>
129        ^ IdentityTransform instance
130    ]
131
132    Transform class >> sequence: transforms [
133        "Return a compound transform, that transforms its visitor by
134        each of the Transforms in transforms in first-to-last order."
135
136	<category: 'instance creation'>
137	transforms isEmpty ifTrue: [ ^self identity ].
138        ^ transforms fold: [:acc :xform | xform after: acc]
139    ]
140
141    initialize [
142	"Overridden by subclasses so that the resulting object represents
143	 the identity transform."
144	<category: 'initializing'>
145    ]
146
147    before: aTransform [
148        "Return a new Transform that transforms transform by self
149         first, then by aTransform."
150
151	<category: 'composing'>
152        ^ aTransform after: self.
153    ]
154
155    accept: aVisitor [
156        "Return a new Transform that transforms transform by
157         aTransform first, then by self."
158
159	<category: 'composing'>
160        self subclassResponsibility
161    ]
162
163    after: transform [
164        "Return a new Transform that transforms transform by
165         aTransform first, then by self."
166
167	<category: 'composing'>
168        self subclassResponsibility
169    ]
170
171    about: aPoint [
172	"Return the transformation described by the receiver, performed
173	 about aPoint rather than about 0@0."
174
175	<category: 'composing'>
176        ^ ((Translation by: aPoint)
177              before: self) before: (Translation by: aPoint * -1)
178    ]
179
180    translateBy: aPoint [
181	"Return the transformation described by the receiver, composed
182	 with a translation by aPoint."
183
184	<category: 'composing'>
185        ^ self asMatrixTransform translateBy: aPoint.
186    ]
187
188    scaleBy: aPoint [
189	"Return the transformation described by the receiver, composed
190	 with scaling by aPoint."
191
192	<category: 'composing'>
193        ^ self asMatrixTransform scaleBy: aPoint.
194    ]
195
196    rotateBy: rads [
197	"Return the transformation described by the receiver, composed
198	 with rotation by rads radians."
199
200	<category: 'composing'>
201        ^ self asMatrixTransform rotateBy: rads.
202    ]
203
204    nullTransform [
205	"Return the transformation described by the receiver, composed
206	 with the identity transform."
207
208	<category: 'composing'>
209	^ self
210    ]
211
212    transformPoint: aPoint [
213	"Answer the result of passing the point aPoint through the receiver."
214
215	<category: 'applying'>
216        self subclassResponsibility
217    ]
218
219    transformDistance: aPoint [
220	"Answer the result of passing the vector aPoint through the receiver."
221
222	<category: 'applying'>
223        self subclassResponsibility
224    ]
225
226    asMatrixTransform [
227	"Answer the receiver converted to a generic matrix-based
228	 transformation."
229
230	<category: 'converting'>
231	self subclassResponsibility
232    ]
233
234    transformBounds: rect [
235        "Transform the given bounds. Note this is distinct from
236         transforming a rectangle, since bounds must be aligned with
237         the axes."
238
239	<category: 'applying'>
240        | corners |
241        corners := {self transformPoint: rect topLeft.
242		    self transformPoint: rect topRight.
243		    self transformPoint: rect bottomLeft.
244		    self transformPoint: rect bottomRight}.
245        ^ (corners fold: [ :left :right | left min: right ]) corner:
246            (corners fold: [ :left :right | left max: right ])
247    ]
248
249    inverse [
250	"Return the inverse transform of the receiver."
251
252	<category: 'composing'>
253        ^ self subclassResponsibility
254    ]
255
256    scale [
257	"Return the scale factor applied by the receiver."
258
259	<category: 'accessing'>
260	^ (1@1)
261     ]
262
263    rotation [
264	"Return the rotation applied by the receiver, in radians."
265
266	<category: 'accessing'>
267	^ 0
268    ]
269
270    translation [
271	"Return the translation applied by the receiver."
272
273	<category: 'accessing'>
274	^ (0@0)
275    ]
276
277    translateTo: aPoint [
278	"Return a version of the receiver that translates 0@0 to aPoint."
279
280	<category: 'composing'>
281	^ self translateBy: (aPoint - self translation).
282    ]
283
284    scaleTo: sxsy [
285	"Return a version of the receiver that scales the distance 1@1 to
286	 sxsy."
287
288	<category: 'composing'>
289	^ self scaleBy: sxsy asPoint / self scale
290    ]
291
292    rotateTo: rads [
293	"Return a version of the receiver that rotates by rads."
294
295	<category: 'composing'>
296	^ self rotateBy: (rads - self rotation)
297    ]
298]
299
300Transform subclass: MatrixTransform [
301    | matrix |
302
303    <category: 'Cairo-Transformation matrices'>
304    <comment: 'I represent transforms using a matrix, in the most generic way.'>
305    asMatrixTransform [
306	"Return the receiver, since it is already a MatrixTransform."
307
308	<category: 'converting'>
309	^self
310    ]
311
312    matrix [
313	<category: 'private-accessing'>
314	^ matrix
315    ]
316
317    postCopy [
318	<category: 'private-copying'>
319        matrix := matrix copy.
320    ]
321
322    copyOp: aBlock [
323	<category: 'private-composing'>
324	| newMatrix |
325	newMatrix := self copy.
326	aBlock value: newMatrix matrix.
327	^newMatrix
328    ]
329
330    initialize [
331	"Initialize the receiver so that it represents the identity transform."
332
333	<category: 'initialize'>
334        matrix := CairoMatrix gcNew initIdentity.
335    ]
336
337    accept: aVisitor [
338        "Sends #transformByMatrix:."
339
340	<category: 'double dispatch'>
341	^aVisitor transformByMatrix: self
342    ]
343
344    after: aTransform [
345        "Return a new Transform that transforms transform by
346         aTransform first, then by self."
347
348	<category: 'composing'>
349	^ aTransform asMatrixTransform
350	    copyOp: [:n | Cairo matrixMultiply: n a: n b: self matrix]
351    ]
352
353    rotateBy: rads [
354	"Return the transformation described by the receiver, composed
355	 with rotation by rads radians."
356
357	<category: 'composing'>
358	^ self copyOp: [:n | Cairo matrixRotate: n radians: rads]
359    ]
360
361    scaleBy: aPoint [
362	"Return the transformation described by the receiver, composed
363	 with scaling by aPoint."
364
365	<category: 'composing'>
366	| p |
367	p := aPoint asPoint.
368	^ self copyOp: [:n | Cairo matrixScale: n sx: p x sy: p y]
369    ]
370
371    translateBy: aPoint [
372	"Return the transformation described by the receiver, composed
373	 with a translation by aPoint."
374
375	<category: 'composing'>
376	^ self copyOp: [:n | Cairo matrixTranslate: n tx: aPoint x ty: aPoint y]
377    ]
378
379    transformPoint: aPoint [
380	"Answer the result of passing the point aPoint through the receiver."
381
382	<category: 'applying'>
383        ^self matrix withPoint: aPoint do:
384            [ :mtx :x :y |
385                Cairo matrixTransformPoint: mtx x: x y: y.
386                x value @ y value
387            ]
388    ]
389
390    transformDistance: aPoint [
391	"Answer the result of passing the vector aPoint through the receiver."
392
393	<category: 'applying'>
394        ^self matrix withPoint: aPoint do:
395            [ :mtx :x :y |
396                Cairo matrixTransformDistance: mtx dx: x dy: y.
397                x value @ y value
398            ]
399    ]
400
401    inverse [
402	"Return the inverse transform of the receiver."
403
404	<category: 'composing'>
405	^ self copyOp: [:n | Cairo matrixInvert: n]
406    ]
407
408    scale [
409	"Return the scale factor applied by the receiver."
410
411	<category: 'accessing'>
412	| pt1 pt2 |
413	pt1 := self transformDistance: (1@0).
414	pt2 := self transformDistance: (0@1).
415	^ (pt1 dist: (0@0)) @ (pt2 dist: (0@0))
416    ]
417
418    rotation [
419	"Return the rotation applied by the receiver, in radians."
420
421	<category: 'accessing'>
422	| pt1 pt2 |
423	pt1 := self transformDistance: (1@0).
424	pt2 := self transformDistance: (0@1).
425	^ pt2 arcTan: pt1
426    ]
427
428    translation [
429	"Return the translation applied by the receiver."
430
431	<category: 'accessing'>
432	^ self transformPoint: (0@0)
433    ]
434]
435
436Transform subclass: AnalyticTransform [
437    | matrix |
438
439    <category: 'Cairo-Transformation matrices'>
440    <comment: 'I represent transforms using its decomposition into scaling,
441rotation and translation.  I am an abstract class.'>
442    transformPoint: aPoint [
443	"Answer the result of passing the point aPoint through the receiver."
444
445	<category: 'applying'>
446        ^self asMatrixTransform transformPoint: aPoint
447    ]
448
449    transformDistance: aPoint [
450	"Answer the result of passing the vector aPoint through the receiver."
451
452	<category: 'applying'>
453        ^(self transformPoint: aPoint) - self translation
454    ]
455
456    asMatrixTransform [
457	"Return the transformation described by the receiver, converted
458	 to a transformation matrix."
459
460	<category: 'converting'>
461        matrix isNil ifTrue: [matrix := self after: MatrixTransform new].
462	^matrix
463    ]
464
465]
466
467AnalyticTransform subclass: IdentityTransform [
468
469    <category: 'Cairo-Transformation matrices'>
470    <comment: 'I represent the identity transform.'>
471    IdentityTransform class [
472        | instance |
473
474        instance [
475	    instance ifNil: [ instance := self new ].
476	    ^instance
477        ]
478    ]
479
480    accept: aVisitor [
481        "Sends #nullTransform."
482
483	<category: 'double dispatch'>
484	^aVisitor nullTransform
485    ]
486
487    before: aTransform [
488        "Return a new Transform that transforms transform by self
489         first, then by aTransform."
490
491	<category: 'composing'>
492	^ aTransform
493    ]
494
495    after: aTransform [
496        "Return a new Transform that transforms transform by
497         aTransform first, then by self."
498
499	<category: 'composing'>
500	^ aTransform
501    ]
502
503    translateBy: aPoint [
504	"Return the transformation described by the receiver, composed
505	 with a translation by aPoint."
506
507	<category: 'composing'>
508	^ Translation by: aPoint
509    ]
510
511    scaleBy: aPoint [
512	"Return the transformation described by the receiver, composed
513	 with scaling by aPoint."
514
515	<category: 'composing'>
516	^ Scale by: aPoint
517    ]
518
519    rotateBy: rads [
520	"Return the transformation described by the receiver, composed
521	 with rotation by rads radians."
522
523	<category: 'composing'>
524	^ Rotation by: rads
525    ]
526
527    transformPoint: aPoint [
528	"Answer the result of passing the point aPoint through the receiver."
529
530	<category: 'applying'>
531	^ aPoint
532    ]
533
534    inverse [
535	"Return the inverse transform of the receiver."
536
537	<category: 'composing'>
538	^ self
539    ]
540]
541
542AnalyticTransform subclass: Translation [
543    | dxdy |
544
545    <category: 'Cairo-Transformation matrices'>
546    <comment: 'I represent translations analytically.'>
547    Translation class >> by: aPoint [
548	"Return an instance of the receiver representing translation by aPoint."
549	<category: 'instance creation'>
550        ^self basicNew
551	    translation: aPoint;
552	    yourself
553    ]
554
555    translation: aPoint [
556	<category: 'private'>
557        dxdy := aPoint.
558    ]
559
560    translateBy: point [
561	"Return the transformation described by the receiver, composed
562	 with a translation by aPoint."
563
564	<category: 'composing'>
565        ^ Translation by: (dxdy + point).
566    ]
567
568    initialize [
569	"Initialize the receiver so that it represents the identity transform."
570
571	<category: 'initializing'>
572	dxdy := 0@0.
573    ]
574
575    accept: aVisitor [
576        "Sends #translateBy:."
577
578	<category: 'double dispatch'>
579	aVisitor translateBy: dxdy.
580    ]
581
582    after: aTransform [
583        "Return a new Transform that transforms transform by
584         aTransform first, then by self."
585
586	<category: 'composing'>
587	^ aTransform translateBy: dxdy.
588    ]
589
590    transformPoint: aPoint [
591	"Answer the result of passing the point aPoint through the receiver."
592
593	<category: 'applying'>
594        ^ aPoint + dxdy
595    ]
596
597    transformDistance: aPoint [
598	"Answer the result of passing the vector aPoint through the receiver."
599
600	<category: 'applying'>
601        ^ aPoint
602    ]
603
604    transformBounds: rect [
605        "Transform the given bounds. This is not distinct from
606         transforming a rectangle in the case of translation."
607
608	<category: 'applying'>
609        ^ rect translateBy: dxdy
610    ]
611
612    inverse [
613	"Return the inverse transform of the receiver."
614
615	<category: 'composing'>
616        ^ Translation by: dxdy * -1
617    ]
618
619    translation [
620	"Return the translation applied by the receiver."
621
622	<category: 'accessing'>
623	^ dxdy
624    ]
625]
626
627AnalyticTransform subclass: Scale [
628    | sxsy |
629
630    <category: 'Cairo-Transformation matrices'>
631    <comment: 'I represent scaling analytically.'>
632    Scale class >> by: aPoint [
633	"Return an instance of the receiver representing scaling by aPoint."
634	<category: 'instance creation'>
635        ^self basicNew
636	    factors: aPoint asPoint;
637	    yourself
638    ]
639
640    factors: aPoint [
641	<category: 'private'>
642        sxsy := aPoint.
643    ]
644
645    scaleBy: factors [
646	"Return the transformation described by the receiver, composed
647	 with scaling by aPoint."
648
649	<category: 'composing'>
650        ^ Scale by: (sxsy * factors)
651    ]
652
653    initialize [
654	"Initialize the receiver so that it represents the identity transform."
655
656	<category: 'initializing'>
657	sxsy := 1@1.
658    ]
659
660    accept: aVisitor [
661        "Sends #scaleBy:."
662
663	<category: 'double dispatch'>
664	aVisitor scaleBy: sxsy.
665    ]
666
667    after: aTransform [
668        "Return a new Transform that transforms transform by
669         aTransform first, then by self."
670
671	<category: 'composing'>
672	^ aTransform scaleBy: sxsy.
673    ]
674
675    transformPoint: aPoint [
676	"Answer the result of passing the point aPoint through the receiver."
677
678	<category: 'applying'>
679        ^ aPoint * sxsy
680    ]
681
682    transformDistance: aPoint [
683	"Answer the result of passing the vector aPoint through the receiver."
684
685	<category: 'applying'>
686        ^ aPoint * sxsy
687    ]
688
689    transformBounds: rect [
690        "Transform the given bounds. This is not distinct from
691         transforming a rectangle in the case of scaling."
692
693        ^ rect scaleBy: sxsy
694    ]
695
696    inverse [
697	"Return the inverse transform of the receiver."
698
699	<category: 'composing'>
700        ^ Scale by: (1/sxsy x) @ (1/sxsy y)
701    ]
702
703    scale [
704	"Return the scale factor applied by the receiver."
705
706	<category: 'accessing'>
707	^ sxsy
708    ]
709]
710
711AnalyticTransform subclass: Rotation [
712    | radians |
713
714    <category: 'Cairo-Transformation matrices'>
715    <comment: 'I represent rotations analytically.'>
716    Rotation class >> by: rads [
717	"Return an instance of the receiver representing rotation by rads
718	 radians."
719	<category: 'instance creation'>
720        ^self basicNew
721	    radians: rads;
722	    yourself
723    ]
724
725    radians: aDouble [
726	<category: 'private'>
727        radians := aDouble.
728    ]
729
730    rotateBy: rads [
731	"Return the transformation described by the receiver, composed
732	 with rotation by rads radians."
733
734	<category: 'composing'>
735        ^ Rotation by: radians + rads.
736    ]
737
738    initialize [
739	"Initialize the receiver so that it represents the identity transform."
740
741	<category: 'initializing'>
742	radians := 0.
743    ]
744
745    accept: aVisitor [
746        "Sends #rotateBy:."
747
748	<category: 'double dispatch'>
749	aVisitor rotateBy: radians.
750    ]
751
752    after: aTransform [
753        "Return a new Transform that transforms transform by
754         aTransform first, then by self."
755
756	<category: 'composing'>
757	^ aTransform rotateBy: radians.
758    ]
759
760    inverse [
761	"Return the inverse transform of the receiver."
762
763	<category: 'composing'>
764        ^ Rotation by: -1 * radians
765    ]
766
767    rotation [
768	"Return the rotation applied by the receiver, in radians."
769
770	<category: 'accessing'>
771	^ radians
772    ]
773]
774