1"======================================================================
2|
3|   Cairo function declarations
4|
5|
6 ======================================================================"
7
8
9"======================================================================
10|
11| Copyright 2008 Free Software Foundation, Inc.
12| Originally by Mike Anderson
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
33
34Object subclass: Cairo [
35
36    <category: 'Cairo-C interface'>
37    <comment: 'This class provides the C functions used in
38calling Cairo functions.  The user should actually use higher-level
39classes such as CairoSurface, CairoPattern and (using #withContextDo:)
40CairoContext.'>
41
42    Cairo class >> arc: cr xc: xc yc: yc radius: radius angle1: angle1 angle2: angle2 [
43        <cCall: 'cairo_arc' returning: #void args: #(#cObject #double #double #double #double #double )>
44    ]
45
46    Cairo class >> arcNegative: cr xc: xc yc: yc radius: radius angle1: angle1 angle2: angle2 [
47        <cCall: 'cairo_arc_negative' returning: #void args: #(#cObject #double #double #double #double #double )>
48    ]
49
50    Cairo class >> clip: cr [
51        <cCall: 'cairo_clip' returning: #void args: #(#cObject )>
52    ]
53
54    Cairo class >> clipPreserve: cr [
55        <cCall: 'cairo_clip_preserve' returning: #void args: #(#cObject )>
56    ]
57
58    Cairo class >> closePath: cr [
59        <cCall: 'cairo_close_path' returning: #void args: #(#cObject )>
60    ]
61
62    Cairo class >> create: target [
63        <cCall: 'cairo_create' returning: #cObject args: #(#cObject )>
64    ]
65
66    Cairo class >> curveTo: cr x1: x1 y1: y1 x2: x2 y2: y2 x3: x3 y3: y3 [
67        <cCall: 'cairo_curve_to' returning: #void args: #(#cObject #double #double #double #double #double #double )>
68    ]
69
70    Cairo class >> destroy: cr [
71        <cCall: 'cairo_destroy' returning: #void args: #(#cObject )>
72    ]
73
74    Cairo class >> fill: cr [
75        <cCall: 'cairo_fill' returning: #void args: #(#cObject )>
76    ]
77
78    Cairo class >> fillPreserve: cr [
79        <cCall: 'cairo_fill_preserve' returning: #void args: #(#cObject )>
80    ]
81
82    Cairo class >> identityMatrix: cr [
83        <cCall: 'cairo_identity_matrix' returning: #void args: #(#cObject )>
84    ]
85
86    Cairo class >> imageSurfaceCreate: format width: width height: height [
87        <cCall: 'cairo_image_surface_create' returning: #cObject args: #(#int #int #int)>
88    ]
89
90    Cairo class >> imageSurfaceCreateForData: data format: format width: width height: height stride: stride [
91        <cCall: 'cairo_image_surface_create_for_data' returning: #cObject args: #(#cObject #int #int #int #int )>
92    ]
93
94    Cairo class >> imageSurfaceCreateFromPng: filename [
95        <cCall: 'cairo_image_surface_create_from_png' returning: #cObject args: #(#string )>
96    ]
97
98    Cairo class >> imageSurfaceGetData: surface [
99        <cCall: 'cairo_image_surface_get_data' returning: #{CByte} args: #(#cObject)>
100    ]
101
102    Cairo class >> imageSurfaceGetHeight: filename [
103        <cCall: 'cairo_image_surface_get_height' returning: #int args: #(#cObject )>
104    ]
105
106    Cairo class >> imageSurfaceGetWidth: filename [
107        <cCall: 'cairo_image_surface_get_width' returning: #int args: #(#cObject )>
108    ]
109
110    Cairo class >> pdfSurfaceCreate: file width: width height: height [
111        <cCall: 'cairo_pdf_surface_create' returning: #cObject args: #(#string #double #double)>
112    ]
113
114    Cairo class >> pdfSurfaceSetSize: file width: width height: height [
115        <cCall: 'cairo_pdf_surface_set_size' returning: #int args: #(#cObject #double #double)>
116    ]
117
118    Cairo class >> svgSurfaceCreate: file width: width height: height [
119        <cCall: 'cairo_svg_surface_create' returning: #cObject args: #(#string #double #double)>
120    ]
121
122    Cairo class >> showPage: file width: width height: height [
123        <cCall: 'cairo_show_page' returning: #void args: #(#cObject)>
124    ]
125
126    Cairo class >> lineTo: cr x: x y: y [
127        <cCall: 'cairo_line_to' returning: #void args: #(#cObject #double #double )>
128    ]
129
130    Cairo class >> mask: cr pattern: pattern [
131        <cCall: 'cairo_mask' returning: #void args: #(#cObject #cObject )>
132    ]
133
134    Cairo class >> maskSurface: cr surface: surface surfaceX: surfaceX surfaceY: surfaceY [
135        <cCall: 'cairo_mask_surface' returning: #void args: #(#cObject #cObject #double #double )>
136    ]
137
138    Cairo class >> matrixInit: matrix xx: xx yx: yx xy: xy yy: yy x0: x0 y0: y0 [
139        <cCall: 'cairo_matrix_init' returning: #void args: #(#cObject #double #double #double #double #double #double )>
140    ]
141
142    Cairo class >> matrixInitIdentity: matrix [
143        <cCall: 'cairo_matrix_init_identity' returning: #void args: #(#cObject )>
144    ]
145
146    Cairo class >> matrixInvert: matrix [
147        <cCall: 'cairo_matrix_invert' returning: #int args: #(#cObject )>
148    ]
149
150    Cairo class >> matrixMultiply: result a: a b: b [
151        <cCall: 'cairo_matrix_multiply' returning: #void args: #(#cObject #cObject #cObject )>
152    ]
153
154    Cairo class >> matrixRotate: matrix radians: radians [
155        <cCall: 'cairo_matrix_rotate' returning: #void args: #(#cObject #double )>
156    ]
157
158    Cairo class >> matrixScale: matrix sx: sx sy: sy [
159        <cCall: 'cairo_matrix_scale' returning: #void args: #(#cObject #double #double )>
160    ]
161
162    Cairo class >> matrixTransformDistance: matrix dx: dx dy: dy [
163        <cCall: 'cairo_matrix_transform_distance' returning: #void args: #(#cObject #cObject #cObject )>
164    ]
165
166    Cairo class >> matrixTransformPoint: matrix x: x y: y [
167        <cCall: 'cairo_matrix_transform_point' returning: #void args: #(#cObject #cObject #cObject )>
168    ]
169
170    Cairo class >> matrixTranslate: matrix tx: tx ty: ty [
171        <cCall: 'cairo_matrix_translate' returning: #void args: #(#cObject #double #double )>
172    ]
173
174    Cairo class >> moveTo: cr x: x y: y [
175        <cCall: 'cairo_move_to' returning: #void args: #(#cObject #double #double )>
176    ]
177
178    Cairo class >> newPath: cr [
179        <cCall: 'cairo_new_path' returning: #void args: #(#cObject )>
180    ]
181
182    Cairo class >> newSubPath: cr [
183        <cCall: 'cairo_new_sub_path' returning: #void args: #(#cObject )>
184    ]
185
186    Cairo class >> paint: cr [
187        <cCall: 'cairo_paint' returning: #void args: #(#cObject )>
188    ]
189
190    Cairo class >> paintWithAlpha: cr alpha: alpha [
191        <cCall: 'cairo_paint_with_alpha' returning: #void args: #(#cObject #double )>
192    ]
193
194    Cairo class >> patternAddColorStopRgba: pattern offset: offset red: red green: green blue: blue alpha: alpha [
195        <cCall: 'cairo_pattern_add_color_stop_rgba' returning: #void args: #(#cObject #double #double #double #double #double )>
196    ]
197
198    Cairo class >> patternCreateForSurface: surface [
199        <cCall: 'cairo_pattern_create_for_surface' returning: #cObject args: #(#cObject )>
200    ]
201
202    Cairo class >> patternCreateLinear: x0 y0: y0 x1: x1 y1: y1 [
203        <cCall: 'cairo_pattern_create_linear' returning: #cObject args: #(#double #double #double #double )>
204    ]
205
206    Cairo class >> patternCreateRadial: cx0 cy0: cy0 radius0: radius0 cx1: cx1 cy1: cy1 radius1: radius1 [
207        <cCall: 'cairo_pattern_create_radial' returning: #cObject args: #(#double #double #double #double #double #double )>
208    ]
209
210    Cairo class >> patternCreateRgb: red green: green blue: blue [
211        <cCall: 'cairo_pattern_create_rgb' returning: #cObject args: #(#double #double #double )>
212    ]
213
214    Cairo class >> patternCreateRgba: red green: green blue: blue alpha: alpha [
215        <cCall: 'cairo_pattern_create_rgba' returning: #cObject args: #(#double #double #double #double )>
216    ]
217
218    Cairo class >> patternReference: pattern [
219        <cCall: 'cairo_pattern_reference' returning: #void args: #(#cObject )>
220    ]
221
222    Cairo class >> patternDestroy: pattern [
223        <cCall: 'cairo_pattern_destroy' returning: #void args: #(#cObject )>
224    ]
225
226    Cairo class >> patternGetExtend: pattern [
227        <cCall: 'cairo_pattern_get_extend' returning: #int args: #(#cObject )>
228    ]
229
230    Cairo class >> patternSetExtend: pattern extend: extend [
231        <cCall: 'cairo_pattern_set_extend' returning: #void args: #(#cObject #int)>
232    ]
233
234    Cairo class >> popGroup: cr [
235        <cCall: 'cairo_pop_group' returning: #cObject args: #(#cObject )>
236    ]
237
238    Cairo class >> pushGroup: cr [
239        <cCall: 'cairo_push_group' returning: #void args: #(#cObject )>
240    ]
241
242    Cairo class >> rectangle: cr x: x y: y width: width height: height [
243        <cCall: 'cairo_rectangle' returning: #void args: #(#cObject #double #double #double #double )>
244    ]
245
246    Cairo class >> reference: cr [
247        <cCall: 'cairo_reference' returning: #cObject args: #(#cObject )>
248    ]
249
250    Cairo class >> relCurveTo: cr dx1: dx1 dy1: dy1 dx2: dx2 dy2: dy2 dx3: dx3 dy3: dy3 [
251        <cCall: 'cairo_rel_curve_to' returning: #void args: #(#cObject #double #double #double #double #double #double )>
252    ]
253
254    Cairo class >> relLineTo: cr dx: dx dy: dy [
255        <cCall: 'cairo_rel_line_to' returning: #void args: #(#cObject #double #double )>
256    ]
257
258    Cairo class >> relMoveTo: cr dx: dx dy: dy [
259        <cCall: 'cairo_rel_move_to' returning: #void args: #(#cObject #double #double )>
260    ]
261
262    Cairo class >> resetClip: cr [
263        <cCall: 'cairo_reset_clip' returning: #void args: #(#cObject )>
264    ]
265
266    Cairo class >> restore: cr [
267        <cCall: 'cairo_restore' returning: #void args: #(#cObject )>
268    ]
269
270    Cairo class >> rotate: cr angle: angle [
271        <cCall: 'cairo_rotate' returning: #void args: #(#cObject #double )>
272    ]
273
274    Cairo class >> save: cr [
275        <cCall: 'cairo_save' returning: #void args: #(#cObject )>
276    ]
277
278    Cairo class >> scale: cr sx: sx sy: sy [
279        <cCall: 'cairo_scale' returning: #void args: #(#cObject #double #double )>
280    ]
281
282    Cairo class >> scaledFontCreate: fontFace fontMatrix: fontMatrix ctm: ctm options: options [
283        <cCall: 'cairo_scaled_font_create' returning: #cObject args: #(#cObject #cObject #cObject #cObject )>
284    ]
285
286    Cairo class >> scaledFontDestroy: scaledFont [
287        <cCall: 'cairo_scaled_font_destroy' returning: #void args: #(#cObject )>
288    ]
289
290    Cairo class >> scaledFontExtents: scaledFont extents: extents [
291        <cCall: 'cairo_scaled_font_extents' returning: #void args: #(#cObject #cObject )>
292    ]
293
294    Cairo class >> scaledFontGetCtm: scaledFont ctm: ctm [
295        <cCall: 'cairo_scaled_font_get_ctm' returning: #void args: #(#cObject #cObject )>
296    ]
297
298    Cairo class >> scaledFontGetFontFace: scaledFont [
299        <cCall: 'cairo_scaled_font_get_font_face' returning: #cObject args: #(#cObject )>
300    ]
301
302    Cairo class >> scaledFontGetFontMatrix: scaledFont fontMatrix: fontMatrix [
303        <cCall: 'cairo_scaled_font_get_font_matrix' returning: #void args: #(#cObject #cObject )>
304    ]
305
306    Cairo class >> scaledFontGetFontOptions: scaledFont options: options [
307        <cCall: 'cairo_scaled_font_get_font_options' returning: #void args: #(#cObject #cObject )>
308    ]
309
310    Cairo class >> scaledFontGetType: scaledFont [
311        <cCall: 'cairo_scaled_font_get_type' returning: #int args: #(#cObject )>
312    ]
313
314    Cairo class >> scaledFontGlyphExtents: scaledFont glyphs: glyphs numGlyphs: numGlyphs extents: extents [
315        <cCall: 'cairo_scaled_font_glyph_extents' returning: #void args: #(#cObject #cObject #int #cObject )>
316    ]
317
318    Cairo class >> scaledFontReference: scaledFont [
319        <cCall: 'cairo_scaled_font_reference' returning: #cObject args: #(#cObject )>
320    ]
321
322    Cairo class >> scaledFontStatus: scaledFont [
323        <cCall: 'cairo_scaled_font_status' returning: #int args: #(#cObject )>
324    ]
325
326    Cairo class >> scaledFontTextExtents: scaledFont utf8: utf8 extents: extents [
327        <cCall: 'cairo_scaled_font_text_extents' returning: #void args: #(#cObject #string #cObject )>
328    ]
329
330    Cairo class >> selectFontFace: cr family: family slant: slant weight: weight [
331        <cCall: 'cairo_select_font_face' returning: #void args: #(#cObject #string #int #int )>
332    ]
333
334    Cairo class >> getSource: cr [
335        <cCall: 'cairo_get_source' returning: #cObject args: #(#cObject )>
336    ]
337
338    Cairo class >> getMiterLimit: cr [
339        <cCall: 'cairo_get_miter_limit' returning: #double args: #(#cObject )>
340    ]
341
342    Cairo class >> getFillRule: cr [
343        <cCall: 'cairo_get_fill_rule' returning: #int args: #(#cObject )>
344    ]
345
346    Cairo class >> getLineCap: cr [
347        <cCall: 'cairo_get_line_cap' returning: #int args: #(#cObject )>
348    ]
349
350    Cairo class >> getLineJoin: cr [
351        <cCall: 'cairo_get_line_join' returning: #int args: #(#cObject )>
352    ]
353
354    Cairo class >> getLineWidth: cr [
355        <cCall: 'cairo_get_line_width' returning: #double args: #(#cObject )>
356    ]
357
358    Cairo class >> getOperator: cr [
359        <cCall: 'cairo_get_operator' returning: #int args: #(#cObject )>
360    ]
361
362    Cairo class >> setSource: cr source: source [
363        <cCall: 'cairo_set_source' returning: #void args: #(#cObject #cObject )>
364    ]
365
366    Cairo class >> setSourceRgb: cr red: red green: green blue: blue [
367        <cCall: 'cairo_set_source_rgb' returning: #void args: #(#cObject #double #double #double )>
368    ]
369
370    Cairo class >> setSourceRgba: cr red: red green: green blue: blue alpha: alpha [
371        <cCall: 'cairo_set_source_rgba' returning: #void args: #(#cObject #double #double #double #double )>
372    ]
373
374    Cairo class >> setFontSize: cr size: size [
375        <cCall: 'cairo_set_font_size' returning: #void args: #(#cObject #double )>
376    ]
377
378    Cairo class >> setMiterLimit: cr miterLimit: size [
379        <cCall: 'cairo_set_miter_limit' returning: #void args: #(#cObject #double )>
380    ]
381
382    Cairo class >> setFillRule: cr fillRule: fillRule [
383        <cCall: 'cairo_set_fill_rule' returning: #void args: #(#cObject #int )>
384    ]
385
386    Cairo class >> setLineCap: cr lineCap: lineCap [
387        <cCall: 'cairo_set_line_cap' returning: #void args: #(#cObject #int )>
388    ]
389
390    Cairo class >> setLineJoin: cr lineJoin: lineJoin [
391        <cCall: 'cairo_set_line_join' returning: #void args: #(#cObject #int )>
392    ]
393
394    Cairo class >> setLineWidth: cr width: width [
395        <cCall: 'cairo_set_line_width' returning: #void args: #(#cObject #double )>
396    ]
397
398    Cairo class >> setOperator: cr operator: lineJoin [
399        <cCall: 'cairo_set_operator' returning: #void args: #(#cObject #int )>
400    ]
401
402    Cairo class >> showText: cr utf8: utf8 [
403        <cCall: 'cairo_show_text' returning: #void args: #(#cObject #string )>
404    ]
405
406    Cairo class >> stroke: cr [
407        <cCall: 'cairo_stroke' returning: #void args: #(#cObject )>
408    ]
409
410    Cairo class >> strokePreserve: cr [
411        <cCall: 'cairo_stroke_preserve' returning: #void args: #(#cObject )>
412    ]
413
414    Cairo class >> surfaceWriteToPng: surface filename: filename [
415        <cCall: 'cairo_surface_write_to_png' returning: #void args: #(#cObject #string )>
416    ]
417
418    Cairo class >> surfaceDestroy: surface [
419        <cCall: 'cairo_surface_destroy' returning: #void args: #(#cObject )>
420    ]
421
422    Cairo class >> surfaceFinish: surface [
423        <cCall: 'cairo_surface_finish' returning: #void args: #(#cObject )>
424    ]
425
426    Cairo class >> surfaceFlush: surface [
427        <cCall: 'cairo_surface_flush' returning: #void args: #(#cObject )>
428    ]
429
430    Cairo class >> textExtents: cr utf8: utf8 extents: extents [
431        <cCall: 'cairo_text_extents' returning: #void args: #(#cObject #string #cObject )>
432    ]
433
434    Cairo class >> textPath: cr utf8: utf8 [
435        <cCall: 'cairo_text_path' returning: #void args: #(#cObject #string )>
436    ]
437
438    Cairo class >> transform: cr matrix: matrix [
439        <cCall: 'cairo_transform' returning: #void args: #(#cObject #cObject )>
440    ]
441
442    Cairo class >> translate: cr tx: tx ty: ty [
443        <cCall: 'cairo_translate' returning: #void args: #(#cObject #double #double )>
444    ]
445
446    Cairo class >> xlibSurfaceSetDrawable: surface drawable: drawable width: width height: height [
447        <cCall: 'cairo_xlib_surface_set_drawable' returning: #void args: #(#cObject #uLong #int #int )>
448    ]
449
450    Cairo class >> xlibSurfaceSetSize: surface width: width height: height [
451        <cCall: 'cairo_xlib_surface_set_size' returning: #void args: #(#cObject #int #int )>
452    ]
453
454    Cairo class >> defaultSelector: aFuncName args: aArgs [
455        <category: 'loading'>
456        | sel |
457        sel := super defaultSelector: aFuncName args: aArgs.
458        (sel startsWith: 'cairo')
459            ifTrue: [sel := (sel at: 6) asLowercase asString , (sel copyFrom: 7)].
460        ^sel
461    ]
462
463    Cairo class >> fillRuleEvenOdd [
464        <category: 'loading'>
465        ^1
466    ]
467
468    Cairo class >> fillRuleWinding [
469        <category: 'loading'>
470        ^0
471    ]
472
473    Cairo class >> lineJoinBevel [
474        <category: 'loading'>
475        ^2
476    ]
477
478    Cairo class >> lineJoinRound [
479        <category: 'loading'>
480        ^1
481    ]
482
483    Cairo class >> lineJoinMiter [
484        <category: 'loading'>
485        ^0
486    ]
487
488    Cairo class >> lineCapSquare [
489        <category: 'loading'>
490        ^2
491    ]
492
493    Cairo class >> lineCapRound [
494        <category: 'loading'>
495        ^1
496    ]
497
498    Cairo class >> lineCapButt [
499        <category: 'loading'>
500        ^0
501    ]
502
503    Cairo class >> fontSlantOblique [
504        <category: 'loading'>
505        ^2
506    ]
507
508    Cairo class >> fontSlantItalic [
509        <category: 'loading'>
510        ^1
511    ]
512
513    Cairo class >> fontSlantNormal [
514        <category: 'loading'>
515        ^0
516    ]
517
518    Cairo class >> fontWeightBold [
519        <category: 'loading'>
520        ^1
521    ]
522
523    Cairo class >> fontWeightNormal [
524        <category: 'loading'>
525        ^0
526    ]
527
528    Cairo class >> extendPad [
529        <category: 'loading'>
530        ^3
531    ]
532
533    Cairo class >> extendReflect [
534        <category: 'loading'>
535        ^2
536    ]
537
538    Cairo class >> extendRepeat [
539        <category: 'loading'>
540        ^1
541    ]
542
543    Cairo class >> extendNone [
544        <category: 'loading'>
545        ^0
546    ]
547
548    Cairo class >> formatArgb32 [
549        <category: 'loading'>
550        ^0
551    ]
552
553    Cairo class >> operatorClear [
554        <category: 'loading'>
555        ^0
556    ]
557
558    Cairo class >> operatorSource [
559        <category: 'loading'>
560        ^1
561    ]
562
563    Cairo class >> operatorOver [
564        <category: 'loading'>
565        ^2
566    ]
567
568    Cairo class >> operatorIn [
569        <category: 'loading'>
570        ^3
571    ]
572
573    Cairo class >> operatorOut [
574        <category: 'loading'>
575        ^4
576    ]
577
578    Cairo class >> operatorAtop [
579        <category: 'loading'>
580        ^5
581    ]
582
583    Cairo class >> operatorDest [
584        <category: 'loading'>
585        ^6
586    ]
587
588    Cairo class >> operatorDestOver [
589        <category: 'loading'>
590        ^7
591    ]
592
593    Cairo class >> operatorDestIn [
594        <category: 'loading'>
595        ^8
596    ]
597
598    Cairo class >> operatorDestOut [
599        <category: 'loading'>
600        ^9
601    ]
602
603    Cairo class >> operatorDestAtop [
604        <category: 'loading'>
605        ^10
606    ]
607
608    Cairo class >> operatorXor [
609        <category: 'loading'>
610        ^11
611    ]
612
613    Cairo class >> operatorAdd [
614        <category: 'loading'>
615        ^12
616    ]
617
618    Cairo class >> operatorSaturate [
619        <category: 'loading'>
620        ^13
621    ]
622
623]
624
625CStruct subclass: CairoTextExtents [
626    <declaration: #(
627        (#xBearing #double)
628        (#yBearing #double)
629        (#width #double)
630        (#height #double)
631        (#xAdvance #double)
632        (#yAdvance #double)) >
633
634    <category: 'Cairo-C interface'>
635]
636