diagrams-cairo-1.3.1.2: Cairo backend for diagrams drawing EDSL

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

Diagrams.Backend.Cairo.CmdLine

Contents

Description

Convenient creation of command-line-driven executables for rendering diagrams using the cairo 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.
  • animMain is like defaultMain but for animations instead of diagrams.
  • gifMain creates an executable to generate an animated GIF.
  • 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.
  • A more flexible approach is to use the renderCairo function provided in the Diagrams.Backend.Cairo module.
  • For the most flexibility, you can call the generic renderDia function directly; see Diagrams.Backend.Cairo for more information.

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

Synopsis

General form of main

The mainWith method unifies all of the other forms of main and is now the recommended way to build a command-line diagrams program. It works as a direct replacement for defaultMain, multiMain, or animMain as well as allowing more general arguments. For example, given a function that produces a diagram when given an Int and a Colour Double, mainWith will produce a program that looks for additional number and color arguments.

... definitions ...
f :: Int -> Colour Double -> Diagram Cairo
f i c = ...

main = mainWith f

We can run this program as follows:

$ ghc --make MyDiagram

# output image.png built by `f 20 red`
$ ./MyDiagram -o image.png -w 200 20 red

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 forms of main

animMain :: Animation Cairo V2 Double -> IO () Source #

animMain is like defaultMain, but renders an animation instead of a diagram. It takes as input an animation and produces a command-line program which will crudely "render" the animation by rendering one image for each frame, named by extending the given output file name by consecutive integers. For example if the given output file name is foo/blah.png, the frames will be saved in foo/blah001.png, foo/blah002.png, and so on (the number of padding digits used depends on the total number of frames). It is up to the user to take these images and stitch them together into an actual animation format (using, e.g. ffmpeg).

Of course, this is a rather crude method of rendering animations; more sophisticated methods will likely be added in the future.

The --fpu option can be used to control how many frames will be output for each second (unit time) of animation.

gifMain :: [(QDiagram Cairo V2 Double Any, GifDelay)] -> IO () Source #

gifMain takes a list of diagram and delay time pairs and produces a command line program to generate an animated GIF, with options GifOpts. "Delay times are in 1/100ths of a second."

Example usage:

  $ ghc --make GifTest
  [1 of 1] Compiling Main             ( GifTest.hs, GifTest.o )
  Linking GifTest ...
  ./GifTest --help
  GifTest

  Usage: GifTest [-w|--width WIDTH] [-h|--height HEIGHT] [-o|--output OUTPUT]
  [--dither] [--looping-off] [--loop-repeat ARG]
  Command-line diagram generation.

  Available options:
   -?,--help                Show this help text
   -w,--width WIDTH         Desired WIDTH of the output image
   -h,--height HEIGHT       Desired HEIGHT of the output image
   -o,--output OUTPUT       OUTPUT file
   --dither                 Turn on dithering.
   --looping-off            Turn looping off
   --loop-repeat ARG        Number of times to repeat

GIF support

data GifOpts Source #

Extra options for animated GIFs.

Constructors

GifOpts 

Instances

Parseable GifOpts Source #

Command line parser for GifOpts. --dither turn dithering on. --looping-off turn looping off, i.e play GIF once. --loop-repeat number of times to repeat the GIF after the first playing. this option is only used if --looping-off is not set.

Backend tokens

data Cairo Source #

This data declaration is simply used as a token to distinguish the cairo backend: (1) when calling functions where the type inference engine would otherwise have no way to know which backend you wanted to use, and (2) as an argument to the Backend and Renderable type classes.

Instances

Eq Cairo Source # 

Methods

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

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

Ord Cairo Source # 

Methods

compare :: Cairo -> Cairo -> Ordering #

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

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

(>) :: Cairo -> Cairo -> Bool #

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

max :: Cairo -> Cairo -> Cairo #

min :: Cairo -> Cairo -> Cairo #

Read Cairo Source # 
Show Cairo Source # 

Methods

showsPrec :: Int -> Cairo -> ShowS #

show :: Cairo -> String #

showList :: [Cairo] -> ShowS #

Backend Cairo V2 Double Source # 
Renderable (Text Double) Cairo Source # 
Renderable (DImage Double Embedded) Cairo Source # 
Renderable (DImage Double External) Cairo Source # 
Renderable (Path V2 Double) Cairo Source # 
Renderable (Trail V2 Double) Cairo Source # 
Show (Options Cairo V2 Double) Source # 
Monoid (Render Cairo V2 Double) Source # 
Hashable (Options Cairo V2 Double) Source # 
Renderable (Segment Closed V2 Double) Cairo Source # 
type V Cairo Source # 
type V Cairo = V2
type N Cairo Source # 
type N Cairo = Double
data Options Cairo V2 Double Source # 
type Result Cairo V2 Double Source # 
type Result Cairo V2 Double = (IO (), Render ())
data Render Cairo V2 Double Source # 
type MainOpts [(String, QDiagram Cairo V2 Double Any)] # 
type MainOpts [(QDiagram Cairo V2 Double Any, GifDelay)] # 
type MainOpts (Animation Cairo V2 Double) # 
type MainOpts (QDiagram Cairo V2 Double Any) # 

type B = Cairo Source #

Orphan instances

Mainable [(String, QDiagram Cairo V2 Double Any)] Source # 
Mainable [(QDiagram Cairo V2 Double Any, GifDelay)] Source # 
Mainable (Animation Cairo V2 Double) Source # 
Mainable (QDiagram Cairo V2 Double Any) Source #