Copyright | Copyright (c) 2015 Anton Pirogov |
---|---|
License | MIT |
Maintainer | anton.pirogov@gmail.com |
Safe Haskell | None |
Language | Haskell2010 |
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
- type Canvas = RenderWrapper Render
- runCanvas :: Canvas a -> Surface -> IO a
- withRenderer :: (forall a. Render a -> IO a) -> V2 Double -> Canvas a -> IO a
- getCanvasSize :: Canvas (V2 Double)
- type Color = V4 Byte
- type Byte = Word8
- gray :: Byte -> Color
- red :: Byte -> Color
- green :: Byte -> Color
- blue :: Byte -> Color
- rgb :: Byte -> Byte -> Byte -> Color
- (!@) :: Color -> Byte -> Color
- stroke :: Color -> Canvas ()
- fill :: Color -> Canvas ()
- noStroke :: Canvas ()
- noFill :: Canvas ()
- strokeWeight :: Double -> Canvas ()
- strokeJoin :: LineJoin -> Canvas ()
- strokeCap :: LineCap -> Canvas ()
- data Dim = D Double Double Double Double
- toD :: V2 Double -> V2 Double -> Dim
- dimPos :: Dim -> V2 Double
- dimSize :: Dim -> V2 Double
- data Anchor
- aligned :: Anchor -> Dim -> Dim
- centered :: Dim -> Dim
- corners :: Dim -> Dim
- background :: Color -> Canvas ()
- point :: V2 Double -> Canvas ()
- line :: V2 Double -> V2 Double -> Canvas ()
- triangle :: V2 Double -> V2 Double -> V2 Double -> Canvas ()
- rect :: Dim -> Canvas ()
- polygon :: [V2 Double] -> Canvas ()
- shape :: ShapeMode -> [V2 Double] -> Canvas ()
- data ShapeMode
- circle :: V2 Double -> Double -> Canvas ()
- circle' :: V2 Double -> Double -> Canvas ()
- arc :: Dim -> Double -> Double -> Canvas ()
- ellipse :: Dim -> Canvas ()
- bezier :: V2 Double -> V2 Double -> V2 Double -> V2 Double -> Canvas ()
- bezierQ :: V2 Double -> V2 Double -> V2 Double -> Canvas ()
- resetMatrix :: Canvas ()
- pushMatrix :: Canvas ()
- popMatrix :: Canvas ()
- translate :: V2 Double -> Canvas ()
- rotate :: Double -> Canvas ()
- scale :: V2 Double -> Canvas ()
- data Image
- createImage :: V2 Int -> Canvas Image
- loadImagePNG :: FilePath -> Canvas Image
- saveImagePNG :: Image -> FilePath -> Canvas ()
- image :: Image -> V2 Double -> Canvas ()
- image' :: Image -> Dim -> Canvas ()
- blend :: Operator -> Image -> Dim -> Dim -> Canvas ()
- grab :: Dim -> Canvas Image
- data Font = Font {}
- textFont :: Font -> Canvas ()
- textSize :: String -> Canvas (V2 Double)
- textExtents :: String -> Canvas (Dim, V2 Double)
- text :: String -> V2 Double -> Canvas (V2 Double)
- text' :: Anchor -> String -> V2 Double -> Canvas (V2 Double)
- mapRange :: Double -> (Double, Double) -> (Double, Double) -> Double
- radians :: Double -> Double
- degrees :: Double -> Double
- randomSeed :: Int -> Canvas ()
- random :: Random a => (a, a) -> Canvas a
- getTime :: IO Time
- data Time = Time {}
- data LineCap :: *
- data LineJoin :: *
Entry point
type Canvas = RenderWrapper Render Source #
wrapper around the Cairo Render
monad, providing a Processing-style API
:: (forall a. Render a -> IO a) | the renderer to use (e.g. |
-> V2 Double | reported canvas size |
-> Canvas a | |
-> IO a |
draw on a Cairo surface using the Canvas
monad
Color and Style
RGBA Color is just a byte vector. Colors can be added, subtracted, etc.
(!@) :: Color -> Byte -> Color Source #
set transparency of color (half red would be: red 255 !@ 128
)
noStroke :: Canvas () Source #
disable stroke (-> shapes without borders!), reenabled by using stroke
strokeWeight :: Double -> Canvas () Source #
set line width for shape borders etc.
strokeJoin :: LineJoin -> Canvas () Source #
set the style of connections between lines of shapes
Coordinates
position (canonically, top-left corner) and size representation (X Y W H)
indicates where a position coordinate is located in a rectangle
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
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
.
(Processing: ShapeMode
beginShape(),vertex(),endShape()
)
Shape mode to use
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
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
Images
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()
)
Text
Font definition
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
Misc
randomSeed :: Int -> Canvas () Source #
set new random seed
get current system time. Use the Time
accessors for specific components.
(Processing: year(),month(),day(),hour(),minute(),second()
)
date and time as returned by getTime
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
Specify how lines join.