static-canvas-0.2.0.0: DSL to generate HTML5 Canvas javascript.

Copyright(c) 2015 Jeffrey Rosenbluth
LicenseBSD-style (see LICENSE)
Maintainerjeffrey.rosenbluth@gmail.com
Safe HaskellNone
LanguageHaskell2010

Graphics.Static

Contents

Description

A small DSL for creating HTML5 Canvas with haskell.

module Main where

import Graphics.Static
import Graphics.Static.ColorNames

text :: CanvasFree ()
text = do
  font "italic 60pt Calibri"
  lineWidth 6
  strokeStyle blue
  fillStyle goldenrod
  textBaseline TextBaselineMiddle
  strokeText "Hello" 25 100 
  fillText "Hello static-canvas!" 25 100

main :: IO ()
main = writeCanvasDoc "example.html" 650 300 text

The static-canvas API shadows the actual Javascript API, and thus the best place to look for a more detailed definition of the canvas functions including the definitions of it's aruments see http://www.w3.org/TR/2dcontext/.

Synopsis

Building and Writing

evalScript :: Text -> CanvasFree a -> Builder Source

Evaluate a static-canvas program and return the javascript code in a Builder. The first parameter should be a unique identifier to avoid name clashes with other canvas elements in the html document.

buildScript :: Int -> Int -> CanvasFree () -> Builder Source

Create a Builder representing a canvas script.

buildScript' :: Int -> Int -> Text -> CanvasFree () -> Builder Source

More general version of buildScript, that takes a unique identifier as an additional parameter so that multiple canvas elements can be included in the same html document.

buildDoc :: Int -> Int -> CanvasFree () -> Builder Source

Create a Builder representing a canvas document.

writeCanvasScript :: FilePath -> Int -> Int -> CanvasFree () -> IO () Source

Write a canvas script element to a file.

writeCanvasScript' :: FilePath -> Int -> Int -> Text -> CanvasFree () -> IO () Source

More general version of writeCanvasScript, that takes a unique identifier as an additional parameter so that multiple canvas elements can be included in the same html document.

writeCanvasDoc :: FilePath -> Int -> Int -> CanvasFree () -> IO () Source

Write a canvas document to a file.

HTML5 Canvas API

type CanvasFree = F Canvas Source

Paths

quadraticCurveTo :: Double -> Double -> Double -> Double -> CanvasFree () Source

A quadratic bezier curve.

bezierCurveTo :: Double -> Double -> Double -> Double -> Double -> Double -> CanvasFree () Source

Cubic Bezier curve.

Line styles

lineWidth :: Double -> CanvasFree () Source

Set the line width.

Colors, styles and shadows

data Gradient Source

Constructors

LG !Int 
RG !Int 

data RepeatStyle Source

For use with createPattern

Constructors

Repeat 
RepeatX 
RepeatY 
NoRepeat 

data Color Source

Constructors

Hex Text 
RGB !Int !Int !Int 
RGBA !Int !Int !Int !Double 

Color utilities

rgb :: Int -> Int -> Int -> Style Source

rgba :: Int -> Int -> Int -> Double -> Style Source

Text

Rectangles

Context

save :: CanvasFree () Source

Push the current state onto the stack.

restore :: CanvasFree () Source

Pop the top state of the stack.

Transformations

Images

onImageLoad :: Int -> CanvasFree () -> CanvasFree () Source

Useful for commands that need to wait for an image to load before being called. For example

image = do
img <- newImage "http://www.staticcanvas.com/picture.png"
onImageLoad img (drawImageAt img 0 0)

Compositing