diagrams-html5-1.4.2: HTML5 canvas backend for diagrams drawing EDSL
Copyright(c) 2015 Jeffrey Rosenbluth
LicenseBSD-style (see LICENSE)
Maintainerdiagrams-discuss@googlegroups.com
Safe HaskellSafe-Inferred
LanguageHaskell2010

Diagrams.Backend.Html5

Contents

Description

A full-featured rendering backend for diagrams using HTML5 Canvas. Implemented using the static-canvas package.

To invoke the Html5 backend, you have three options.

  • You can use the Diagrams.Backend.Html5.CmdLine module to create standalone executables which will display the diagram in a browser using a web service.
  • You can use the renderHtml5 function provided by this module, which gives you more programmatic control over when and how images are displayed (making it east to, for example, write a single program that displays multiple images, or one that diaplays images dynamically based on user input, and so on).
  • For the most flexiblity you can invoke the renderDia method from Backend instance for Html5. In particular, renderDia has the generic type
renderDia :: b -> Options b v -> QDiagram b v m -> Result b v

(omitting a few type class contraints). b represents the backend type, v the vector space, and m the type of monoidal query annotations on the diagram. Options and Result are associated data and type families, respectively, which yield the type of option records and rendering results specific to any particular backend. For b ~ Html5 and v ~ R2, we have

data Options Html5 V2 Double = Html5Options
 { _size :: SizeSpec V2 -- ^^ The requested size
 }
data family Render Html5 V2 Double = C (RenderM ())
type family Result Html5 V2 Double = Html5 ()

So the type of renderDia resolves to

renderDia :: Html5 -> Options Html5 V2 Double -> QDiagram Html5 V2 Double m ->
Html5()

which you could call like renderDia Html5 (Html5Options (width 250)) myDiagram

Synopsis

Documentation

data Html5 Source #

This data declaration is simply used as a token to distinguish this rendering engine.

Constructors

Html5 

Instances

Instances details
Read Html5 Source # 
Instance details

Defined in Diagrams.Backend.Html5

Show Html5 Source # 
Instance details

Defined in Diagrams.Backend.Html5

Methods

showsPrec :: Int -> Html5 -> ShowS #

show :: Html5 -> String #

showList :: [Html5] -> ShowS #

Eq Html5 Source # 
Instance details

Defined in Diagrams.Backend.Html5

Methods

(==) :: Html5 -> Html5 -> Bool #

(/=) :: Html5 -> Html5 -> Bool #

Ord Html5 Source # 
Instance details

Defined in Diagrams.Backend.Html5

Methods

compare :: Html5 -> Html5 -> Ordering #

(<) :: Html5 -> Html5 -> Bool #

(<=) :: Html5 -> Html5 -> Bool #

(>) :: Html5 -> Html5 -> Bool #

(>=) :: Html5 -> Html5 -> Bool #

max :: Html5 -> Html5 -> Html5 #

min :: Html5 -> Html5 -> Html5 #

Backend Html5 V2 Double Source # 
Instance details

Defined in Diagrams.Backend.Html5

Associated Types

data Render Html5 V2 Double #

type Result Html5 V2 Double #

data Options Html5 V2 Double #

Mainable [(String, QDiagram Html5 V2 Double Any)] Source # 
Instance details

Defined in Diagrams.Backend.Html5.CmdLine

Associated Types

type MainOpts [(String, QDiagram Html5 V2 Double Any)] #

Renderable (Text Double) Html5 Source # 
Instance details

Defined in Diagrams.Backend.Html5

Renderable (Path V2 Double) Html5 Source # 
Instance details

Defined in Diagrams.Backend.Html5

Renderable (Trail V2 Double) Html5 Source # 
Instance details

Defined in Diagrams.Backend.Html5

Renderable (DImage Double External) Html5 Source # 
Instance details

Defined in Diagrams.Backend.Html5

Monoid (Render Html5 V2 Double) Source # 
Instance details

Defined in Diagrams.Backend.Html5

Semigroup (Render Html5 V2 Double) Source # 
Instance details

Defined in Diagrams.Backend.Html5

Renderable (Segment Closed V2 Double) Html5 Source # 
Instance details

Defined in Diagrams.Backend.Html5

Mainable (QDiagram Html5 V2 Double Any) Source # 
Instance details

Defined in Diagrams.Backend.Html5.CmdLine

Associated Types

type MainOpts (QDiagram Html5 V2 Double Any) #

type N Html5 Source # 
Instance details

Defined in Diagrams.Backend.Html5

type N Html5 = Double
type V Html5 Source # 
Instance details

Defined in Diagrams.Backend.Html5

type V Html5 = V2
data Options Html5 V2 Double Source # 
Instance details

Defined in Diagrams.Backend.Html5

data Render Html5 V2 Double Source # 
Instance details

Defined in Diagrams.Backend.Html5

data Render Html5 V2 Double = C (RenderM ())
type Result Html5 V2 Double Source # 
Instance details

Defined in Diagrams.Backend.Html5

type MainOpts [(String, QDiagram Html5 V2 Double Any)] Source # 
Instance details

Defined in Diagrams.Backend.Html5.CmdLine

type MainOpts (QDiagram Html5 V2 Double Any) Source # 
Instance details

Defined in Diagrams.Backend.Html5.CmdLine

type B = Html5 Source #

data family Options b (v :: Type -> Type) n #

Backend-specific rendering options.

Instances

Instances details
data Options NullBackend v n 
Instance details

Defined in Diagrams.Core.Types

data Options Html5 V2 Double Source # 
Instance details

Defined in Diagrams.Backend.Html5

Lenses

canvasId :: Lens' (Options Html5 V2 Double) String Source #

"id" for the canvas element (prepended to "StaticCanvas"). Only applies to non-standalone diagrams.

standalone :: Lens' (Options Html5 V2 Double) Bool Source #

Should the output be a standalone html file. Otherwise the output is a canvas element followed by a script calling the canvas.