cairo-canvas-0.1.0.0: Simpler drawing API for Cairo.

CopyrightCopyright (c) 2015 Anton Pirogov
LicenseMIT
Maintaineranton.pirogov@gmail.com
Safe HaskellNone
LanguageHaskell2010

Graphics.Rendering.Cairo.Canvas

Contents

Description

This module defines the Canvas monad, which is a convenience wrapper around the underlying Cairo rendering and can be used with the same textures. You can also mix both APIs, if the need arises.

The Canvas API imitates most of the drawing functions of the Processing language. See http://processing.org/reference for comparison. While having the Processing spirit, this module does not aim for a perfect mapping and deviates where necessary or appropriate. Nevertheless most Processing examples should be trivial to port to the Canvas API. Example:

{-# LANGUAGE OverloadedStrings #-}
import SDL
import SDL.Cairo
import Linear.V2 (V2(..))
import Graphics.Rendering.Cairo.Canvas

main :: IO ()
main = do
  initializeAll
  window <- createWindow "cairo-canvas using SDL2" defaultWindow
  renderer <- createRenderer window (-1) defaultRenderer
  texture <- createCairoTexture' renderer window

  withCairoTexture' texture $ runCanvas $ do
    background $ gray 102
    fill $ red 255 !@ 128
    noStroke
    rect $ D 200 200 100 100
    stroke $ green 255 !@ 128
    fill $ blue 255 !@ 128
    rect $ D 250 250 100 100
    triangle (V2 400 300) (V2 350 400) (V2 400 400)

  copy renderer texture Nothing Nothing
  present renderer
  delay 5000

Synopsis

Entry point

type Canvas = RenderWrapper Render Source #

wrapper around the Cairo Render monad, providing a Processing-style API

runCanvas :: Canvas a -> Surface -> IO a Source #

draw on a Cairo surface using the Canvas monad

withRenderer Source #

Arguments

:: (forall a. Render a -> IO a)

the renderer to use (e.g. renderWith surface)

-> V2 Double

reported canvas size

-> Canvas a 
-> IO a 

draw on a Cairo surface using the Canvas monad

getCanvasSize :: Canvas (V2 Double) Source #

get size of the canvas (Processing: width(), height())

Color and Style

type Color = V4 Byte Source #

RGBA Color is just a byte vector. Colors can be added, subtracted, etc.

type Byte = Word8 Source #

For values from 0 to 255

gray :: Byte -> Color Source #

create opaque gray color

red :: Byte -> Color Source #

create opaque red color

green :: Byte -> Color Source #

create opaque green color

blue :: Byte -> Color Source #

create opaque blue color

rgb :: Byte -> Byte -> Byte -> Color Source #

create opaque mixed color

(!@) :: Color -> Byte -> Color Source #

set transparency of color (half red would be: red 255 !@ 128)

stroke :: Color -> Canvas () Source #

set current stroke color

fill :: Color -> Canvas () Source #

set current fill color

noStroke :: Canvas () Source #

disable stroke (-> shapes without borders!), reenabled by using stroke

noFill :: Canvas () Source #

disable fill (-> shapes are not filled!), reenabled by using fill

strokeWeight :: Double -> Canvas () Source #

set line width for shape borders etc.

strokeJoin :: LineJoin -> Canvas () Source #

set the style of connections between lines of shapes

strokeCap :: LineCap -> Canvas () Source #

set the style of the line caps

Coordinates

data Dim Source #

position (canonically, top-left corner) and size representation (X Y W H)

Constructors

D Double Double Double Double 

Instances

Eq Dim Source # 

Methods

(==) :: Dim -> Dim -> Bool #

(/=) :: Dim -> Dim -> Bool #

Show Dim Source # 

Methods

showsPrec :: Int -> Dim -> ShowS #

show :: Dim -> String #

showList :: [Dim] -> ShowS #

toD :: V2 Double -> V2 Double -> Dim Source #

create dimensions from position and size vector

dimPos :: Dim -> V2 Double Source #

get position vector from dimensions

dimSize :: Dim -> V2 Double Source #

get size vector from dimensions

data Anchor Source #

indicates where a position coordinate is located in a rectangle

Constructors

NW 
N 
NE 
E 
SE 
S 
SW 
W 
Center 
Baseline 

Instances

aligned :: Anchor -> Dim -> Dim Source #

takes dimensions with non-standard position coordinate, returns dimensions normalized to top-left corner coordinate

centered :: Dim -> Dim Source #

takes dimensions with centered position, returns normalized (top-left corner)

corners :: Dim -> Dim Source #

takes dimensions with bottom-right corner instead of size, returns normalized (with size)

Primitives

background :: Color -> Canvas () Source #

clear the canvas with given color

point :: V2 Double -> Canvas () Source #

draw a point with stroke color (cairo emulates this with 1x1 rects!)

line :: V2 Double -> V2 Double -> Canvas () Source #

draw a line between two points with stroke color

triangle :: V2 Double -> V2 Double -> V2 Double -> Canvas () Source #

draw a triangle connecting three points

rect :: Dim -> Canvas () Source #

draw a rectangle

polygon :: [V2 Double] -> Canvas () Source #

draw a polygon connecting given points (equivalent to shape (ShapeRegular True))

shape :: ShapeMode -> [V2 Double] -> Canvas () Source #

draw shape along a given path using given ShapeMode. (Processing: beginShape(),vertex(),endShape())

data ShapeMode Source #

Shape mode to use

Constructors

ShapeRegular Bool

regular path. flag decides whether the first and last point are connected

ShapePoints

just draw the points, no lines

ShapeLines

interpret points as pairs, draw lines

ShapeTriangles

interpret points as triples, draw triangles

ShapeTriangleStrip

draw triangle for every neighborhood of 3 points

ShapeTriangleFan

fix first point, draw triangles with every neighboring pair and first point

Arcs and Curves

circle :: V2 Double -> Double -> Canvas () Source #

draw circle: circle leftCorner diameter

circle' :: V2 Double -> Double -> Canvas () Source #

draw circle: circle centerPoint diameter

arc :: Dim -> Double -> Double -> Canvas () Source #

draw arc: arc dimensions startAngle endAngle

ellipse :: Dim -> Canvas () Source #

draw ellipse

bezier :: V2 Double -> V2 Double -> V2 Double -> V2 Double -> Canvas () Source #

draw cubic bezier spline: bezier fstAnchor fstControl sndControl sndAnchor

bezierQ :: V2 Double -> V2 Double -> V2 Double -> Canvas () Source #

draw quadratic bezier spline: bezier fstAnchor control sndAnchor

Transformations

resetMatrix :: Canvas () Source #

replace current matrix with identity

pushMatrix :: Canvas () Source #

push current matrix onto the stack

popMatrix :: Canvas () Source #

pop a matrix

translate :: V2 Double -> Canvas () Source #

translate coordinate system

rotate :: Double -> Canvas () Source #

rotate coordinate system

scale :: V2 Double -> Canvas () Source #

scale coordinate system

Images

data Image Source #

Stores an image surface with additional information

createImage :: V2 Int -> Canvas Image Source #

create a new empty image of given size

loadImagePNG :: FilePath -> Canvas Image Source #

load a PNG image from given path.

saveImagePNG :: Image -> FilePath -> Canvas () Source #

Save an image as PNG to given file path

image :: Image -> V2 Double -> Canvas () Source #

Render complete image on given coordinates

image' :: Image -> Dim -> Canvas () Source #

Render complete image inside given dimensions

blend :: Operator -> Image -> Dim -> Dim -> Canvas () Source #

Copy given part of image to given part of screen, using given blending operator and resizing when necessary. Use OperatorSource to copy without blending effects. (Processing: copy(),blend())

grab :: Dim -> Canvas Image Source #

get a copy of the image from current window (Processing: get())

Text

data Font Source #

Font definition

Constructors

Font 

Instances

Eq Font Source # 

Methods

(==) :: Font -> Font -> Bool #

(/=) :: Font -> Font -> Bool #

Show Font Source # 

Methods

showsPrec :: Int -> Font -> ShowS #

show :: Font -> String #

showList :: [Font] -> ShowS #

textFont :: Font -> Canvas () Source #

set current font for text rendering

textSize :: String -> Canvas (V2 Double) Source #

get the size of the text when rendered in current font

textExtents :: String -> Canvas (Dim, V2 Double) Source #

get information about given text when rendered in current font. returns tuple with location of top-left corner relative to the origin and size of rendered text in the first component, cursor advancement relative to origin in the second component (also see TextExtents).

text :: String -> V2 Double -> Canvas (V2 Double) Source #

render text. returns cursor advancement (text = text' Baseline)

text' :: Anchor -> String -> V2 Double -> Canvas (V2 Double) Source #

render text with specified alignment. returns cursor advancement

Math

mapRange :: Double -> (Double, Double) -> (Double, Double) -> Double Source #

map a value from one range onto another

radians :: Double -> Double Source #

convert degrees to radians

degrees :: Double -> Double Source #

convert radians to degrees

Misc

randomSeed :: Int -> Canvas () Source #

set new random seed

random :: Random a => (a, a) -> Canvas a Source #

get new random number

getTime :: IO Time Source #

get current system time. Use the Time accessors for specific components. (Processing: year(),month(),day(),hour(),minute(),second())

data Time Source #

date and time as returned by getTime

Constructors

Time 

Fields

Instances

Eq Time Source # 

Methods

(==) :: Time -> Time -> Bool #

(/=) :: Time -> Time -> Bool #

Show Time Source # 

Methods

showsPrec :: Int -> Time -> ShowS #

show :: Time -> String #

showList :: [Time] -> ShowS #

data LineCap :: * #

Specify line endings.

LineCapButt
Start(stop) the line exactly at the start(end) point.
LineCapRound
Use a round ending, the center of the circle is the end point.
LineCapSquare
Use squared ending, the center of the square is the end point