diagrams-svg-1.0.1.2: SVG backend for diagrams drawing EDSL.

Maintainerdiagrams-discuss@googlegroups.com
Safe HaskellNone

Diagrams.Backend.SVG.CmdLine

Contents

Description

Convenient creation of command-line-driven executables for rendering diagrams using the SVG 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 subtable 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.
  • You can use renderSVG to render a diagram to a file directly; see Diagrams.Backend.SVG.
  • A more flexible approach is to directly call renderDia; see Diagrams.Backend.SVG 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 or multiMain 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 SVG R2
 f i c = ...

 main = mainWith f

We can run this program as follows:

 $ ghc --make MyDiagram
 
 # output image.svg built by `f 20 red`
 $ ./MyDiagram -o image.svg -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

defaultMain :: Diagram SVG R2 -> IO ()Source

This is the simplest way to render diagrams, and is intended to be used like so:

 ... definitions ...

 main = defaultMain myDiagram

Compiling this file will result in an executable which takes various command-line options for setting the size, output file, and so on, and renders myDiagram with the specified options.

Pass --help to the generated executable to see all available options. Currently it looks something like

 ./Program

Usage: ./Program [-w|--width WIDTH] [-h|--height HEIGHT] [-o|--output OUTPUT] [--loop] [-s|--src ARG] [-i|--interval INTERVAL]
   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
   -l,--loop                Run in a self-recompiling loop
   -s,--src ARG             Source file to watch
   -i,--interval INTERVAL   When running in a loop, check for changes every INTERVAL seconds.

For example, a common scenario is

 $ ghc --make MyDiagram

# output image.svg with a width of 400pt (and auto-determined height)
 $ ./MyDiagram -o image.svg -w 400

multiMain :: [(String, Diagram SVG R2)] -> IO ()Source

multiMain is like defaultMain, except instead of a single diagram it takes a list of diagrams paired with names as input. The generated executable then takes a --selection option specifying the name of the diagram that should be rendered. The list of available diagrams may also be printed by passing the option --list.

Example usage:

 $ ghc --make MultiTest
 [1 of 1] Compiling Main             ( MultiTest.hs, MultiTest.o )
 Linking MultiTest ...
 $ ./MultiTest --list
 Available diagrams:
   foo bar
 $ ./MultiTest --selection bar -o Bar.eps -w 200

Backend tokens

data SVG Source

SVG is simply a token used to identify this rendering backend (to aid type inference).

type B = SVGSource