diagrams-canvas-1.4: HTML5 canvas backend for diagrams drawing EDSL

Copyright(c) 2011-2014 Diagrams team (see LICENSE)
LicenseBSD-style (see LICENSE)
Maintainerdiagrams-discuss@googlegroups.com
Safe HaskellNone
LanguageHaskell2010

Diagrams.Backend.Canvas.CmdLine

Contents

Description

Convenient creation of command-line-driven executables for rendering diagrams using the Canvas backend.

  • defaultMain creates an executable which can render a single diagram at various options.
  • multiMain is like defaultMain but allows for a list of diagrams from which the user can choose one to render.
  • mainWith is a generic form that does all of the above but with a slightly scarier type. See Diagrams.Backend.CmdLine. This form can also take a function type that has a suitable final result (any of arguments to the above types) and Parseable arguments.

If you want to generate diagrams programmatically---i.e. if you want to do anything more complex than what the below functions provide---you have several options.

  • Use a function with mainWith. This may require making Parseable instances for custom argument types.
  • Make a new Mainable instance. This may require a newtype wrapper on your diagram type to avoid the existing instances. This gives you more control over argument parsing, intervening steps, and diagram creation.
  • Build option records and pass them along with a diagram to mainRender from Diagrams.Backend.CmdLine.

For a tutorial on command-line diagram creation see http://projects.haskell.org/diagrams/doc/cmdline.html.

Synopsis

General form of main

mainWith :: (Mainable d, Parseable (MainOpts d)) => d -> IO () #

Main entry point for command-line diagram creation. This is the method that users will call from their program main. For instance an expected user program would take the following form.

import Diagrams.Prelude
import Diagrams.Backend.TheBestBackend.CmdLine

d :: Diagram B R2
d = ...

main = mainWith d

Most backends should be able to use the default implementation. A different implementation should be used to handle more complex interactions with the user.

Supported froms of main

data Canvas Source #

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

Instances

Eq Canvas Source # 

Methods

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

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

Ord Canvas Source # 
Read Canvas Source # 
Show Canvas Source # 
Backend Canvas V2 Double Source # 
Renderable (Text Double) Canvas Source # 
Renderable (DImage Double External) Canvas Source # 
Renderable (Path V2 Double) Canvas Source # 
Renderable (Trail V2 Double) Canvas Source # 
Monoid (Render Canvas V2 Double) Source # 
Renderable (Segment Closed V2 Double) Canvas Source # 
type V Canvas Source # 
type V Canvas = V2
type N Canvas Source # 
type N Canvas = Double
data Options Canvas V2 Double Source # 
type Result Canvas V2 Double Source # 
data Render Canvas V2 Double Source # 
data Render Canvas V2 Double = C (RenderM ())
type MainOpts [(String, QDiagram Canvas V2 Double Any)] # 
type MainOpts (QDiagram Canvas V2 Double Any) # 

type B = Canvas Source #

Orphan instances