blank-canvas-0.5: HTML5 Canvas Graphics Library

Safe HaskellNone
LanguageHaskell2010

Graphics.Blank

Contents

Description

blank-canvas is a Haskell binding to the complete HTML5 Canvas API. blank-canvas allows Haskell users to write, in Haskell, interactive images onto their web browsers. blank-canvas gives the users a single full-window canvas, and provides many well-documented functions for rendering images.

Synopsis

Starting blank-canvas

blankCanvas :: Options -> (DeviceContext -> IO ()) -> IO () Source

blankCanvas is the main entry point into blank-canvas. A typical invocation would be

{-# LANGUAGE OverloadedStrings #-}
module Main where

import Graphics.Blank

main = blankCanvas 3000 $ \ context -> do
        send context $ do
                moveTo(50,50)
                lineTo(200,100)
                lineWidth 10
                strokeStyle "red"
                stroke()

data Options Source

Constructors

Options 

Fields

port :: Int

which port do we issue the blank canvas using

events :: [EventName]

which events does the canvas listen to

debug :: Bool

turn on debugging (default False)

root :: String

location of the static files (default .)

middleware :: [Middleware]

extra middleware(s) to be executed. (default [local_only])

Instances

sending to the Graphics DeviceContext

data DeviceContext Source

Context is our abstact handle into a specific 2d-context inside a browser. Note that the JavaScript API concepts of 2D-Context and Canvas are conflated in blank-canvas. Therefore, there is no getContext method, rather getContext is implied (when using send).

Instances

send :: DeviceContext -> Canvas a -> IO a Source

Sends a set of Canvas commands to the canvas. Attempts to common up as many commands as possible. Should not crash.

HTML5 Canvas API

Canvas element

height :: (Image image, Num a) => image -> a Source

width :: (Image image, Num a) => image -> a Source

toDataURL :: () -> Canvas Text Source

Turn the canvas into a png data stream / data URL.

"data:image/png;base64,iVBORw0KGgo.."

2D Context

save :: () -> Canvas () Source

restore :: () -> Canvas () Source

Transformation

Image drawing

class Image a Source

Minimal complete definition

jsImage, width, height

drawImage :: Image image => (image, [Double]) -> Canvas () Source

drawImage' takes 2, 4, or 8 Double arguments. See drawImageAt, drawImageSize, and drawImageCrop for variants with exact numbers of arguments.

Compositing

Line styles

data LineEndCap Source

The style of the caps on the endpoints of a line.

Constructors

ButtCap

Flat edges

RoundCap

Semicircular end caps

SquareCap

Square end caps

data LineJoinCorner Source

The style of corner that is created when two lines join.

Constructors

BevelCorner

A filled triangle with a beveled edge connects two lines.

RoundCorner

A filled arc connects two lines.

MiterCorner

A filled triangle with a sharp edge connects two lines.

Colors, styles and shadows

data RepeatDirection Source

The direction in which a CanvasPattern repeats.

Constructors

Repeat

The pattern repeats both horizontally and vertically.

RepeatX

The pattern repeats only horizontally.

RepeatY

The pattern repeats only vertically.

NoRepeat

The pattern displays only once and does not repeat.

data CanvasGradient Source

A handle to the CanvasGradient. CanvasGradients can not be destroyed.

data CanvasPattern Source

A handle to the CanvasPattern. CanvasPatterns can not be destroyed.

Paths

beginPath :: () -> Canvas () Source

closePath :: () -> Canvas () Source

fill :: () -> Canvas () Source

stroke :: () -> Canvas () Source

clip :: () -> Canvas () Source

Text

data TextAnchorAlignment Source

The anchor point for text in the current DeviceContext.

Constructors

StartAnchor

The text is anchored at either its left edge (if the canvas is left-to-right) or its right edge (if the canvas is right-to-left).

EndAnchor

The text is anchored at either its right edge (if the canvas is left-to-right) or its left edge (if the canvas is right-to-left).

CenterAnchor

The text is anchored in its center.

LeftAnchor

The text is anchored at its left edge.

RightAnchor

the text is anchored at its right edge.

data TextMetrics Source

The width argument of TextMetrics can trivially be projected out.

Constructors

TextMetrics Double 

Instances

Rectangles

Pixel manipulation

getImageData :: (Double, Double, Double, Double) -> Canvas ImageData Source

Capture ImageDate from the Canvas.

putImageData :: (ImageData, [Double]) -> Canvas () Source

putImageData takes 2 or 6 Double arguments. See putImageDataAt and putImageDataDirty for variants with exact numbers of arguments.

data ImageData Source

ImageData is a transliteration of the JavaScript ImageData, There are two Ints, and one (unboxed) Vector of Word8s. width, height, data can be projected from ImageData, length can be used to find the length.

Note: ImageData lives on the server, not the client.

Constructors

ImageData !Int !Int !(Vector Word8) 

blank-canvas Extensions

Reading from Canvas

newImage :: Text -> Canvas CanvasImage Source

image takes a URL (perhaps a data URL), and returns the CanvasImage handle, _after_ loading. The assumption is you are using local images, so loading should be near instant.

data CanvasImage Source

A handle to the Image. CanvasImages can not be destroyed.

DeviceContext attributes

CanvasContext, and off-screen Canvas.

data CanvasContext Source

A handle to an offscreen canvas. CanvasContext can not be destroyed.

newCanvas :: (Int, Int) -> Canvas CanvasContext Source

Create a new, off-screen canvas buffer. Takes width and height.

with :: CanvasContext -> Canvas a -> Canvas a Source

with runs a set of canvas commands in the context of a specific canvas buffer.

myCanvasContext :: Canvas CanvasContext Source

myCanvasContext returns the current CanvasContent.

Syncing

sync :: Canvas () Source

Send all commands to the browser, wait for the browser to ack, then continue.

Debugging

console_log :: JSArg msg => msg -> Canvas () Source

console_log aids debugging by sending the argument to the browser console.log.

eval :: Text -> Canvas () Source

eval executes the argument in JavaScript directly.

Drawing Utilities

clearCanvas :: Canvas () Source

Clear the screen. Restores the default transformation matrix.

saveRestore :: Canvas a -> Canvas a Source

Wrap a canvas computation in save / restore.

(#) :: a -> (a -> Canvas b) -> Canvas b infixr 0 Source

The #-operator is the Haskell analog to the .-operator in Javascript. Example:

grd # addColorStop(0, "#8ED6FF");

This can be seen as equivalent of grd.addColorStop(0, "#8ED6FF").

readDataURL :: Text -> FilePath -> IO Text Source

Read a file, and generate a data URL.

 url <- readDataURL "image/png" "image/foo.png"

dataURLMimeType :: Text -> Text Source

Find the mime type for a data URL.

> dataURLMimeType "data:image/png;base64,iVBORw..."
"image/png"

writeDataURL :: FilePath -> Text -> IO () Source

Write a data URL to a given file.

drawImageAt :: Image image => (image, Double, Double) -> Canvas () Source

Draws an image onto the canvas at the given x- and y-coordinates.

drawImageSize :: Image image => (image, Double, Double, Double, Double) -> Canvas () Source

Acts like drawImageAt, but with two extra Double arguments. The third and fourth Doubles specify the width and height of the image, respectively.

drawImageCrop :: Image image => (image, Double, Double, Double, Double, Double, Double, Double, Double) -> Canvas () Source

Acts like drawImageSize, but with four extra Double arguments before the arguments of drawImageSize. The first and second Doubles specify the x- and y-coordinates at which the image begins to crop. The third and fourth Doubles specify the width and height of the cropped image.

drawImageCrop img 0 0 dw dh dx dy dw dh = drawImageSize = dx dy dw dh

putImageDataAt :: (ImageData, Double, Double) -> Canvas () Source

Writes ImageData to the canvas at the given x- and y-coordinates.

putImageDataDirty :: (ImageData, Double, Double, Double, Double, Double, Double) -> Canvas () Source

Acts like putImageDataDirty, but with four extra Double arguments that specify which region of the ImageData (the dirty rectangle) should be drawn. The third and fourth Doubles specify the dirty rectangle's x- and y- coordinates, and the fifth and sixth Doubles specify the dirty rectangle's width and height.

putImageDataDirty imgData dx dy 0 0 w h = putImageDataAt imgData dx dy
  where (w, h) = case imgData of ImageData w' h' _ -> (w', h')

Events

trigger :: Event -> Canvas () Source

trigger a specific named event, please.

eventQueue :: DeviceContext -> EventQueue Source

A single (typed) event queue

wait :: DeviceContext -> IO Event Source

wait for any event. blocks.

flush :: DeviceContext -> IO [Event] Source

flush all the current events, returning them all to the user. Never blocks.

data Event Source

Basic Event from Browser; see http://api.jquery.com/category/events/ for details.

Constructors

Event 

type EventName = Text Source

EventName mirrors event names from jquery, and use lower case. Possible named events

  • keypress, keydown, keyup
  • mouseDown, mouseenter, mousemove, mouseout, mouseover, mouseup

type EventQueue = TChan Event Source

EventQueue is a STM channel (TChan) of Events. Intentionally, EventQueue is not abstract.

Middleware