static-canvas: DSL to generate HTML5 Canvas javascript.

[ bsd3, graphics, library ] [ Propose Tags ]

A simple DSL for writing HTML5 Canvas in haskell and converting it to Javascript. By static we mean non-interactive, so the parts of the Canvas API that need to query the browser for run time information like `isPointInPath(x, y)` are not included. This turns out to be a surprisingly small part of HTML5 Canvas.


[Skip to Readme]

Downloads

Maintainer's Corner

Package maintainers

For package maintainers and hackage trustees

Candidates

  • No Candidates
Versions [RSS] 0.1.0.0, 0.2.0.0, 0.2.0.1, 0.2.0.2, 0.2.0.3
Dependencies base (>=4.5 && <4.9), double-conversion (>=2.0 && <2.1), free (>=4.9 && <4.11), mtl (>=2.1 && <2.3), text (>=0.11 && <1.3) [details]
License BSD-3-Clause
Copyright 2015 Jeffrey Rosenbluth
Author Jeffrey Rosenbluth
Maintainer jeffrey.rosenbluth@gmail.com
Category Graphics
Home page https://github.com/jeffreyrosenbluth/static-canvas
Bug tracker https://github.com/jeffreyrosenbluth/static-canvas/issues
Uploaded by jeffreyrosenbluth at 2015-02-14T03:43:30Z
Distributions LTSHaskell:0.2.0.3, NixOS:0.2.0.3
Reverse Dependencies 2 direct, 0 indirect [details]
Downloads 5235 total (20 in the last 30 days)
Rating (no votes yet) [estimated by Bayesian average]
Your Rating
  • λ
  • λ
  • λ
Status Docs available [build log]
Last success reported on 2015-02-14 [all 1 reports]

Readme for static-canvas-0.2.0.0

[back to package description]

static-canvas Hackage

A simple DSL for writing HTML5 Canvas in haskell and converting it to Javascript. By static we mean non-interactive, so the parts of the Canvas API that need to query the browser for run time information like isPointInPath(x, y) are not included. This turns out to be a surprisingly small part of HTML5 Canvas.

Here is Hello static-canvas with fancy text.

Text

{-# LANGUAGE OverloadedStrings #-}

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" 150 100 
  fillText "Hello World!" 150 100

main :: IO ()
main = writeCanvasDoc "Text.html" 600 400 text

There are plenty of examples in Examples. Here is one more showing how to use pattern to fill a rectangle.

line

{-# LANGUAGE OverloadedStrings #-}

module Main where

import Graphics.Static

pattern :: CanvasFree ()
pattern = do
  img <- newImage "tile.png"
  onImageLoad img $ do
    ptn <- createPattern img Repeat
    rect 0 0 400 400
    fillStyle ptn
    fill

main :: IO ()
main = writeCanvasDoc "Pattern.html" 400 400 pattern