blank-canvas-0.3.1: HTML5 Canvas Graphics Library

Safe HaskellNone

Graphics.Blank

Contents

Synopsis

Starting blank-canvas

blankCanvas :: Int -> (Context -> IO ()) -> IO ()Source

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

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()

Graphics Context

data Context Source

Context is our abstact handle into a specific 2d-context inside a browser.

send :: Context -> Canvas a -> IO aSource

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

Drawing pictures using the Canvas DSL

fill :: () -> Canvas ()Source

restore :: () -> Canvas ()Source

save :: () -> Canvas ()Source

stroke :: () -> Canvas ()Source

readEvent :: EventName -> Canvas EventSource

read a specific event; wait for it if the event is not in queue. **Thows away all other events while waiting.**

readEvents :: [EventName] -> Canvas NamedEventSource

read a specific set of events; wait for it if the event/events is not in queue. **Throws away all other non-named events while waiting.**

tryReadEvent :: EventName -> Canvas (Maybe Event)Source

read a specific event. **Throws away all events not named**

tryReadEvents :: [EventName] -> Canvas (Maybe NamedEvent)Source

read a specific set of events. **Throws away all non-named events while waiting.**

size :: Canvas (Float, Float)Source

size of the canvas

Events

data Event Source

Basic Event from Browser, the code is event-type specific.

Constructors

Event 

Fields

jsCode :: Int
 
jsMouse :: Maybe (Int, Int)
 

Instances

data EventName Source

EventName mirrors event names from jquery, where 'map toLower (show name)' gives the jquery event name.

data NamedEvent Source

When an event is sent to the application, it always has a name.

Constructors

NamedEvent EventName Event 

type EventQueue = TChan NamedEventSource

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