diagrams-svg-1.4.3.1: SVG backend for diagrams drawing EDSL.
Copyright(c) 2013 Diagrams team (see LICENSE)
LicenseBSD-style (see LICENSE)
Maintainerdiagrams-discuss@googlegroups.com
Safe HaskellNone
LanguageHaskell2010

Diagrams.Backend.SVG.CmdLine

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 https://diagrams.github.io/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 V2 Double
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 => 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

Backend tokens

data SVG Source #

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

Instances

Instances details
Show SVG Source # 
Instance details

Defined in Diagrams.Backend.SVG

Methods

showsPrec :: Int -> SVG -> ShowS #

show :: SVG -> String #

showList :: [SVG] -> ShowS #

SVGFloat n => Backend SVG V2 n Source # 
Instance details

Defined in Diagrams.Backend.SVG

Associated Types

data Render SVG V2 n #

type Result SVG V2 n #

data Options SVG V2 n #

SVGFloat n => Mainable [(String, QDiagram SVG V2 n Any)] Source # 
Instance details

Defined in Diagrams.Backend.SVG.CmdLine

Associated Types

type MainOpts [(String, QDiagram SVG V2 n Any)] #

SVGFloat n => Renderable (Text n) SVG Source # 
Instance details

Defined in Diagrams.Backend.SVG

Methods

render :: SVG -> Text n -> Render SVG (V (Text n)) (N (Text n)) #

SVGFloat n => Renderable (DImage n Embedded) SVG Source # 
Instance details

Defined in Diagrams.Backend.SVG

Methods

render :: SVG -> DImage n Embedded -> Render SVG (V (DImage n Embedded)) (N (DImage n Embedded)) #

SVGFloat n => Renderable (Path V2 n) SVG Source # 
Instance details

Defined in Diagrams.Backend.SVG

Methods

render :: SVG -> Path V2 n -> Render SVG (V (Path V2 n)) (N (Path V2 n)) #

Eq n => Eq (Options SVG V2 n) Source # 
Instance details

Defined in Diagrams.Backend.SVG

Methods

(==) :: Options SVG V2 n -> Options SVG V2 n -> Bool #

(/=) :: Options SVG V2 n -> Options SVG V2 n -> Bool #

Semigroup (Render SVG V2 n) Source # 
Instance details

Defined in Diagrams.Backend.SVG

Methods

(<>) :: Render SVG V2 n -> Render SVG V2 n -> Render SVG V2 n #

sconcat :: NonEmpty (Render SVG V2 n) -> Render SVG V2 n #

stimes :: Integral b => b -> Render SVG V2 n -> Render SVG V2 n #

Monoid (Render SVG V2 n) Source # 
Instance details

Defined in Diagrams.Backend.SVG

Methods

mempty :: Render SVG V2 n #

mappend :: Render SVG V2 n -> Render SVG V2 n -> Render SVG V2 n #

mconcat :: [Render SVG V2 n] -> Render SVG V2 n #

Hashable n => Hashable (Options SVG V2 n) Source # 
Instance details

Defined in Diagrams.Backend.SVG

Methods

hashWithSalt :: Int -> Options SVG V2 n -> Int #

hash :: Options SVG V2 n -> Int #

SVGFloat n => Mainable (QDiagram SVG V2 n Any) Source # 
Instance details

Defined in Diagrams.Backend.SVG.CmdLine

Associated Types

type MainOpts (QDiagram SVG V2 n Any) #

type V SVG Source # 
Instance details

Defined in Diagrams.Backend.SVG

type V SVG = V2
type N SVG Source # 
Instance details

Defined in Diagrams.Backend.SVG

type N SVG = Double
data Options SVG V2 n Source # 
Instance details

Defined in Diagrams.Backend.SVG

newtype Render SVG V2 n Source # 
Instance details

Defined in Diagrams.Backend.SVG

newtype Render SVG V2 n = R (SvgRenderM n)
type Result SVG V2 n Source # 
Instance details

Defined in Diagrams.Backend.SVG

type Result SVG V2 n = Element
type MainOpts [(String, QDiagram SVG V2 n Any)] Source # 
Instance details

Defined in Diagrams.Backend.SVG.CmdLine

type MainOpts (QDiagram SVG V2 n Any) Source # 
Instance details

Defined in Diagrams.Backend.SVG.CmdLine

type B = SVG Source #

Orphan instances

SVGFloat n => Mainable [(String, QDiagram SVG V2 n Any)] Source # 
Instance details

Associated Types

type MainOpts [(String, QDiagram SVG V2 n Any)] #

SVGFloat n => Mainable (QDiagram SVG V2 n Any) Source # 
Instance details

Associated Types

type MainOpts (QDiagram SVG V2 n Any) #