Cairo__GraphicsContext.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Wed, 07 Jan 2015 12:02:09 +0100
changeset 32 fb983be8d2c0
parent 31 26070c1e480e
child 33 8a2e438b4363
permissions -rw-r--r--
To fold - support for display/fillArc...

"{ Package: 'stx:goodies/libcairo' }"

"{ NameSpace: Cairo }"

Smalltalk::GraphicsContext subclass:#GraphicsContext
	instanceVariableNames:'handle surface'
	classVariableNames:'Lobby SymbolicFontSlantToCairoFontSlantMap'
	poolDictionaries:'Cairo::FontSlant Cairo::FontWeight Cairo::Format'
	category:'Cairo-Objects'
!


!GraphicsContext class methodsFor:'initialization'!

initialize
    "Invoked at system start or when the class is dynamically loaded."

    "/ please change as required (and remove this comment)

    Lobby := Registry new.

    SymbolicFontSlantToCairoFontSlantMap := Dictionary new.
    SymbolicFontSlantToCairoFontSlantMap at: 'normal' put: CAIRO_FONT_SLANT_NORMAL.
    SymbolicFontSlantToCairoFontSlantMap at: 'italic' put: CAIRO_FONT_SLANT_ITALIC.

    "Modified: / 29-12-2014 / 01:06:39 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!GraphicsContext class methodsFor:'instance creation'!

onSurface: surface

    | handle |

    self
        assert: (surface isKindOf: Cairo::Surface)
        message: 'surface is not valid Cairo surface'.

    handle := CPrimitives cairo_create: surface.
    ^ self new initializeWithHandle: handle surface: surface

    "Created: / 28-12-2014 / 23:45:36 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!GraphicsContext class methodsFor:'accessing'!

dllPath

    OperatingSystem isMSWINDOWSlike ifTrue:[
        ^ #( 'C:\Windows' 'C:\Windows\System32' "Wild guess, should not harm" )
    ].

    OperatingSystem isUNIXlike ifTrue:[
        OperatingSystem getSystemType == #linux ifTrue:[
            | path |

            path := #( '/lib' '/usr/lib' '/usr/local/lib' ).
            (OperatingSystem getSystemInfo at:#machine) = 'x86_64' ifTrue:[
                "If the machine is 64bit, prepend standard path for 32bit libs.
                 Leave standard paths at the end, as the system might be completely
                 32bit but running on 64bit-capable CPU.

                CAVEAT: This is bit dangerous, as on 64bit OS, if ia32 libs are
                not installed byt 64bit sqlite libs are, then 64bit libs are found
                and when a function is called, segfault will occur!!

                Q: Is there a way how to figure out if the OS itself is 32bit,
                regardles on CPU?"
                path := #( '/lib32' '/usr/lib32' '/usr/local/lib32' ) , path.
            ].
            ^path

        ].
    ].

    self error:'Unsupported operating system'

    "
        SqliteLibrary dllPath
    "

    "Created: / 31-08-2011 / 18:02:17 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

libraryName

    OperatingSystem isUNIXlike ifTrue:[^'libcairo.so.2'].

    OperatingSystem isMSWINDOWSlike ifTrue:[^'cairo.dll'].

    self error:'Library name for host OS is not known'
!

sizeof
    "Returns size of undelaying structure in bytes"

    ^0
! !

!GraphicsContext class methodsFor:'examples'!

rectangleOnTranscript

    "
        Cairo::GraphicsContext rectangleOnTranscript
    "


    | gc |
    gc := Transcript cairo.
    gc paint: Color black.
    gc moveToX: 30 y: 50.
    gc paint: (Color red alpha: 0.5).
    gc rectangleX: 10 y: 15 width: 150 height: 60.
    gc fill.
    gc paint: (Color red alpha: 0.75).
    gc rectangleX: 10 y: 15 width: 150 height: 60.
    gc stroke.

    "Created: / 23-04-2009 / 17:33:57 / Jan Vrany <vranyj1@fel.cvut.cz>"
! !

!GraphicsContext methodsFor:'accessing'!

device
    ^ device

    "Created: / 29-12-2014 / 18:44:59 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

deviceClippingBoundsOrNil
    ^ clipRect

    "Created: / 02-01-2015 / 12:36:58 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

drawableId
    ^ surface drawable

    "Created: / 02-01-2015 / 12:37:31 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

font:aFont
    | family slant weight |

    font := aFont onDevice: device.
    aFont isAlienFont ifTrue:[ 

    ] ifFalse:[ 
        family := font family.
        slant := SymbolicFontSlantToCairoFontSlantMap at: font style ifAbsent:[ CAIRO_FONT_SLANT_NORMAL ].
        weight := CAIRO_FONT_WEIGHT_NORMAL.

        self font: family slant: slant weight: weight.
        self fontSize: font size.
    ]

    "Modified: / 02-01-2015 / 12:34:36 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

function:aFunctionSymbol
    "set the drawing function"

    ^ self shouldImplement
!

lineWidth: w
    lineWidth ~~ w ifTrue:[  
        super lineWidth: w. 
        CPrimitives cairo_set_line_width: handle _:w asFloat
    ].

    "Created: / 17-06-2012 / 21:55:05 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 02-01-2015 / 00:18:15 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

mask:aForm
    "set the drawing mask"

    ^ self shouldImplement
!

paint: aColor

"/    paint ~= aColor ifTrue:[  
        paint := aColor ? Black.
        CPrimitives cairo_set_source_rgba: handle _: (paint red / 100) asDouble _: (paint green / 100) asDouble _: (paint blue / 100) asDouble _: paint alpha asDouble
"/    ].

    "Created: / 10-07-2008 / 11:18:13 / Jan Vrany <vranyj1@fel.cvut.cz>"
    "Modified: / 23-04-2009 / 17:31:33 / Jan Vrany <vranyj1@fel.cvut.cz>"
    "Modified: / 02-01-2015 / 00:51:20 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

referenceCount
    "Return value or reference counter"

    ^ CPrimitives cairo_get_reference_count: handle

    "Created: / 28-12-2014 / 22:11:29 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

surface
    ^surface

    "Created: / 10-07-2008 / 10:33:59 / Jan Vrany <vranyj1@fel.cvut.cz>"
    "Modified: / 10-09-2008 / 20:53:00 / Jan Vrany <vranyj1@fel.cvut.cz>"
    "Modified: / 28-12-2014 / 23:59:03 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!GraphicsContext methodsFor:'accessing-path properties'!

lineCap: lc

    ^ CPrimitives cairo_set_line_cap: handle _: lc

    "Created: / 17-06-2012 / 22:09:19 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 28-12-2014 / 21:58:08 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!GraphicsContext methodsFor:'accessing-transformation'!

transformation:aTransformation 
    "set the transformation"

    super transformation: aTransformation.
    CPrimitives cairo_identity_matrix: handle.
    transformation notNil ifTrue:[
        CPrimitives cairo_translate: handle _: transformation translationX asFloat _: transformation translationY asFloat.
        CPrimitives cairo_scale: handle _: transformation scaleX asFloat _: transformation scaleY asFloat.        
    ] ifFalse:[ 
        CPrimitives cairo_translate: handle _: 0.0 _: 0.0.
        CPrimitives cairo_scale: handle _: 1.0 _: 1.0.        
    ].

    "Created: / 01-01-2015 / 12:07:07 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 07-01-2015 / 11:58:41 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!GraphicsContext methodsFor:'basic drawing'!

displayArcX:x y:y width:w height:h from:start angle:angle

    | angle1 angle2 |

    self save.    
    w ~~ h ifTrue:[
        self notYetImplemented
    ].

    angle1 := (360 - start) .
    angle2 := (360 - (start + angle)) \\ 360.

    (angle2 < angle1) ifTrue:[
        self arcNegativeX: (x + (w / 2)) y: (y + (h / 2)) radius: w / 2 from: angle1 * (Float pi / 180) to: angle2 * (Float pi / 180).
    ] ifFalse:[ 
        self arcNegativeX: (x + (w / 2)) y: (y + (h / 2)) radius: w / 2 from: angle2 * (Float pi / 180) to: angle1 * (Float pi / 180).
    ].
    self stroke.

    w ~~ h ifTrue:[
        self notYetImplemented
    ].
    self restore.

    "Modified: / 07-01-2015 / 11:58:26 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

displayLineFromX:x0 y:y0 toX:x1 y:y1
    "draw a line from x0/y0 to x1/y1"

    self moveToX: x0 y: y0.
    self lineToX: x1 y: y1.
    self stroke.

    "Modified: / 29-12-2014 / 01:18:06 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

displayOpaqueString:aString from:index1 to:index2 x:x y:y
    "draw part of a string with both fg and bg at x/y in current font"

    ^ self shouldImplement
!

displayOpaqueString:aString from:index1 to:index2 x:x y:y maxWitdh:maxWidth
    "draw part of a string with both fg and bg at x/y in current font"

    ^ self shouldImplement
!

displayPolygon:points
    "draw a polygon
     - this could be recoded to draw using displayLine"

    self moveToX: points first x asFloat y: points first y asFloat.
    2 to: points size do:[:i |  
        self lineToX: (points at: i) x asFloat  y: (points at: i) y asFloat
    ].
    self closePath.
    self stroke.

    "Modified: / 02-01-2015 / 01:46:41 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

displayRectangleX:x y:y width:w height:h
    "draw a rectangle
     - this could be recoded to draw using displayLine"

    self rectangleX: x y: y width: w height: h.
    self stroke.

    "Modified: / 29-12-2014 / 01:18:36 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

displayString:aString from:index1 to:index2 x:x y:y
    "draw part of a string with fg at x/y in current font"

    font isAlienFont ifTrue:[ 
        font displayString:aString from:index1 to:index2 x:x y:y in:self.  
    ] ifFalse:[  
        self save.
        self moveToX: x y: y.
        (index1 == 1 and:[ index2 == aString size ]) ifTrue:[ 
            self showText: aString
        ] ifFalse:[ 
            self showText: (aString copyFrom: index1 to: index2).
        ].
        self restore.
    ]

    "Modified: / 02-01-2015 / 12:36:30 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!GraphicsContext methodsFor:'basic filling'!

fillArcX:x y:y width:w height:h from:start angle:angle

    | angle1 angle2 |

    self save.    
    w ~~ h ifTrue:[
        self notYetImplemented
    ].


    angle1 := (360 - start) .
    angle2 := (360 - (start + angle)) \\ 360.

    self moveToX: (x + (w / 2)) y: (y + (h / 2)).

    (angle2 < angle1) ifTrue:[
        self arcNegativeX: (x + (w / 2)) y: (y + (h / 2)) radius: w / 2 from: angle1 * (Float pi / 180) to: angle2 * (Float pi / 180).
    ] ifFalse:[ 
        self arcNegativeX: (x + (w / 2)) y: (y + (h / 2)) radius: w / 2 from: angle2 * (Float pi / 180) to: angle1 * (Float pi / 180).
    ].
    self closePath.

    self strokeAndPreserve.
    self fill.

    w ~~ h ifTrue:[

    ].
    self restore.

    "Modified: / 07-01-2015 / 04:25:15 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

fillPolygon:points
    "fill a polygon with current paint color"

    self moveToX: points first x asFloat y: points first y asFloat.
    2 to: points size do:[:i |  
        self lineToX: (points at: i) x asFloat  y: (points at: i) y asFloat
    ].
    self closePath.
    self strokeAndPreserve.
    self fill.

    "Modified: / 02-01-2015 / 01:45:54 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

fillRectangleX:x y:y width:w height:h
    "fill a rectangle with current paint color"

    self rectangleX: x y: y width: w height: h. 
    self strokeAndPreserve.
    self fill.

    "Modified: / 02-01-2015 / 00:32:06 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!GraphicsContext methodsFor:'bit blitting'!

copyFrom:aGC x:srcX y:srcY toX:dstX y:dstY width:w height:h
    "copy from a drawable - maybe self"

    ^ self shouldImplement
! !

!GraphicsContext methodsFor:'cairo api - paths'!

arcNegativeX: x y: y radius: r from: startAngle to: stopAngle

    ^CPrimitives cairo_arc_negative: handle _: x asDouble _: y asDouble _: r asDouble _: startAngle asDouble _: stopAngle asDouble

    "Created: / 07-01-2015 / 02:35:10 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

arcX: x y: y radius: r from: startAngle to: stopAngle

    ^CPrimitives cairo_arc: handle _: x asDouble _: y asDouble _: r asDouble _: startAngle asDouble _: stopAngle asDouble

    "Created: / 17-06-2012 / 21:50:10 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 28-12-2014 / 22:00:18 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

closePath
    ^CPrimitives cairo_close_path: handle.

    "Created: / 01-01-2015 / 22:42:30 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

lineToX: x y: y

    ^CPrimitives cairo_line_to: handle _: x asDouble _: y asDouble

    "Created: / 17-06-2012 / 22:15:22 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 28-12-2014 / 22:00:30 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

moveToX: x y: y

    ^CPrimitives cairo_move_to: handle _: x asDouble _: y asDouble

    "Created: / 23-04-2009 / 17:21:00 / Jan Vrany <vranyj1@fel.cvut.cz>"
    "Modified: / 28-12-2014 / 22:00:42 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

rectangleX: x y: y width: w height: h
    | rx ry rw rh |

    rx := x.
    ry := y.
    rw := w.
    rh := h.
    rw < 0 ifTrue:[ 
        rx := rx + rw.
        rw := rw abs.
    ].
    rh < 0 ifTrue:[ 
        ry := ry + rh.
        rh := rh abs.
    ].                 

    ^CPrimitives cairo_rectangle: handle
        _: rx asDouble
        _: ry asDouble
        _: rw asDouble
        _: rh asDouble

    "Created: / 10-07-2008 / 09:41:50 / Jan Vrany <vranyj1@fel.cvut.cz>"
    "Modified: / 02-01-2015 / 01:21:59 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!GraphicsContext methodsFor:'cairo api - patterns'!

setSourceSurface: aSurface
    ^ self setSourceSurface: aSurface x: 0.0 y: 0.0

    "Created: / 24-12-2014 / 23:12:32 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

setSourceSurface: aSyrface x:x y:y
    "raise an error: this method should be implemented (TODO)"

    ^ CPrimitives cairo_set_source_surface: handle _: aSyrface _: x _: y

    "Created: / 24-12-2014 / 23:12:32 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 28-12-2014 / 21:59:20 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!GraphicsContext methodsFor:'cairo api - save & restore'!

restore
    ^CPrimitives cairo_restore: handle

    "Created: / 17-06-2012 / 21:51:38 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 28-12-2014 / 22:01:15 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

save
    ^CPrimitives cairo_save: handle

    "Created: / 17-06-2012 / 21:51:29 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 28-12-2014 / 22:01:22 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!GraphicsContext methodsFor:'cairo api - stroke & fill'!

draw
    "Fills whole surface. 

     This method calls  cairo_paint(), however, #paint is defined in 
     GraphicsContext as method returning current foreground color/pattern."
    
    ^ CPrimitives cairo_paint:handle.

    "Created: / 29-12-2014 / 11:28:58 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

fill

    ^CPrimitives cairo_fill: handle

    "Created: / 10-07-2008 / 09:42:50 / Jan Vrany <vranyj1@fel.cvut.cz>"
    "Modified: / 28-12-2014 / 22:01:30 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

fillAndPreserve

    ^CPrimitives cairo_fill_preserve: handle

    "Created: / 17-06-2012 / 21:52:04 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 28-12-2014 / 22:01:41 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

showPage
    "Makes sense only for PDF surfaces"

    ^CPrimitives cairo_show_page: handle.

    "Created: / 17-06-2012 / 08:44:14 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 28-12-2014 / 22:02:00 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

stroke

    ^CPrimitives cairo_stroke: handle

    "Created: / 10-07-2008 / 09:42:43 / Jan Vrany <vranyj1@fel.cvut.cz>"
    "Modified: / 28-12-2014 / 22:02:10 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

strokeAndPreserve

    ^CPrimitives cairo_stroke_preserve: handle

    "Created: / 17-06-2012 / 21:52:21 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 28-12-2014 / 22:15:40 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!GraphicsContext methodsFor:'cairo api - text'!

font: family slant: slant weight: weight

    ^CPrimitives cairo_select_font_face: handle
        _: family asString
        _: slant asInteger
        _: weight asInteger

    "Created: / 29-12-2014 / 01:08:50 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

fontSize: sz

    ^CPrimitives cairo_set_font_size: handle _: sz asFloat

    "Created: / 23-04-2009 / 17:24:33 / Jan Vrany <vranyj1@fel.cvut.cz>"
    "Modified: / 02-01-2015 / 01:39:43 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

showText: aString

    ^CPrimitives cairo_show_text: handle _: aString utf8Encoded

    "Created: / 23-04-2009 / 17:25:20 / Jan Vrany <vranyj1@fel.cvut.cz>"
    "Modified: / 28-12-2014 / 22:02:36 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!GraphicsContext methodsFor:'cairo api - transformations & clipping'!

clip

    ^CPrimitives cairo_clip: handle.

    "Created: / 17-06-2012 / 21:56:58 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 28-12-2014 / 22:02:45 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!GraphicsContext methodsFor:'drawing'!

displayForm:aFormOrImage x:x y:y
    "draw a form (or image) at x/y; 
     if the form has depth 1, 1's in the form are
     drawn in current paint color, 0's are ignored.
     If the form has depth ~~ 1, the current fg color setting is ignored."

    | image width height stride data image_surface |

    image := aFormOrImage asImage.
    width := image width.
    height := image height.
    stride := CPrimitives cairo_format_stride_for_width: CAIRO_FORMAT_ARGB32 _: width.
    data := ExternalBytes basicNew allocateBytes: stride * height clear: false.
    [
        image bitsARGB32Into: data stride: stride fg: self paint bg:  self backgroundPaint. 
        image_surface := CPrimitives cairo_image_surface_create_for_data: data _: CAIRO_FORMAT_ARGB32 _: width _: height _: stride.
        CPrimitives cairo_set_source_surface: handle _: image_surface _: x asFloat _: y asFloat.
        CPrimitives cairo_paint: handle.
    ] ensure:[ 
        data finalize.
        image_surface release.
    ].

    "Created: / 31-12-2014 / 12:08:08 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 01-01-2015 / 02:48:32 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!GraphicsContext methodsFor:'initialize & release'!

destroy
    "Tell Cairo library to destroy the corresponding C object.
     Remember that object is physically destroyed only if internal
     refcounter goes to zero. However, after calling destroy,
     this instance should be treated as invalid."

    ^ CPrimitives cairo_destroy: handle

    "Created: / 28-12-2014 / 22:10:19 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

initializeWithHandle:anExternalAddress surface: aSurface
    handle := anExternalAddress.
    surface := aSurface.
    device := aSurface device.
    self lineWidth: 1.
    self initialize.
    self font: font.

    "Created: / 28-12-2014 / 23:52:38 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 02-01-2015 / 00:20:22 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

release
    ^self destroy

    "Created: / 28-12-2014 / 23:49:00 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!GraphicsContext class methodsFor:'documentation'!

version
    ^'$Id$'
!

version_HG
    ^ '$Changeset: <not expanded> $'
! !


GraphicsContext initialize!