diagrams-rasterific-1.4.1.1: Rasterific backend for diagrams.

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

Diagrams.Backend.Rasterific.CmdLine

Contents

Description

Convenient creation of command-line-driven executables for rendering diagrams using the Rasterific backend. Create png, tif, bmp, jpg, pdf, or animated GIF files.

  • 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.

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 => 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 Rasterific 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 :: [(Diagram Rasterific, GifDelay)] -> IO () Source #

Make an animated gif main by pairing diagrams with a delay (Int measured in 100th seconds).

uniformGifMain :: GifDelay -> [Diagram Rasterific] -> IO () Source #

Make an animated gif main with the same delay for each diagram.

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.

Instance details

Defined in Diagrams.Backend.Rasterific.CmdLine

Backend tokens

data Rasterific Source #

This data declaration is simply used as a token to distinguish the Rasterific 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 Rasterific Source # 
Instance details

Defined in Diagrams.Backend.Rasterific

Ord Rasterific Source # 
Instance details

Defined in Diagrams.Backend.Rasterific

Read Rasterific Source # 
Instance details

Defined in Diagrams.Backend.Rasterific

Show Rasterific Source # 
Instance details

Defined in Diagrams.Backend.Rasterific

TypeableFloat n => Backend Rasterific V2 n Source # 
Instance details

Defined in Diagrams.Backend.Rasterific

Associated Types

data Render Rasterific V2 n :: * #

type Result Rasterific V2 n :: * #

data Options Rasterific V2 n :: * #

ToResult [(QDiagram Rasterific V2 n Any, GifDelay)] #

An animated GIF can be a result.

Instance details

Defined in Diagrams.Backend.Rasterific.CmdLine

Associated Types

type Args [(QDiagram Rasterific V2 n Any, GifDelay)] :: * #

type ResultOf [(QDiagram Rasterific V2 n Any, GifDelay)] :: * #

TypeableFloat n => Mainable [(String, QDiagram Rasterific V2 n Any)] # 
Instance details

Defined in Diagrams.Backend.Rasterific.CmdLine

Associated Types

type MainOpts [(String, QDiagram Rasterific V2 n Any)] :: * #

TypeableFloat n => Mainable [(QDiagram Rasterific V2 n Any, GifDelay)] # 
Instance details

Defined in Diagrams.Backend.Rasterific.CmdLine

Associated Types

type MainOpts [(QDiagram Rasterific V2 n Any, GifDelay)] :: * #

TypeableFloat n => Renderable (Text n) Rasterific Source # 
Instance details

Defined in Diagrams.Backend.Rasterific

Methods

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

TypeableFloat n => Renderable (DImage n Embedded) Rasterific Source # 
Instance details

Defined in Diagrams.Backend.Rasterific

TypeableFloat n => Renderable (Path V2 n) Rasterific Source # 
Instance details

Defined in Diagrams.Backend.Rasterific

Methods

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

Show n => Show (Options Rasterific V2 n) Source # 
Instance details

Defined in Diagrams.Backend.Rasterific

Semigroup (Render Rasterific V2 n) Source # 
Instance details

Defined in Diagrams.Backend.Rasterific

Monoid (Render Rasterific V2 n) Source # 
Instance details

Defined in Diagrams.Backend.Rasterific

TypeableFloat n => Mainable (Animation Rasterific V2 n) # 
Instance details

Defined in Diagrams.Backend.Rasterific.CmdLine

Associated Types

type MainOpts (Animation Rasterific V2 n) :: * #

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

Defined in Diagrams.Backend.Rasterific

TypeableFloat n => Mainable (QDiagram Rasterific V2 n Any) # 
Instance details

Defined in Diagrams.Backend.Rasterific.CmdLine

Associated Types

type MainOpts (QDiagram Rasterific V2 n Any) :: * #

type V Rasterific Source # 
Instance details

Defined in Diagrams.Backend.Rasterific

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

Defined in Diagrams.Backend.Rasterific

data Options Rasterific V2 n Source # 
Instance details

Defined in Diagrams.Backend.Rasterific

data Render Rasterific V2 n Source # 
Instance details

Defined in Diagrams.Backend.Rasterific

data Render Rasterific V2 n = R (RenderM n ())
type Result Rasterific V2 n Source # 
Instance details

Defined in Diagrams.Backend.Rasterific

type ResultOf [(QDiagram Rasterific V2 n Any, GifDelay)] # 
Instance details

Defined in Diagrams.Backend.Rasterific.CmdLine

type Args [(QDiagram Rasterific V2 n Any, GifDelay)] # 
Instance details

Defined in Diagrams.Backend.Rasterific.CmdLine

type MainOpts [(String, QDiagram Rasterific V2 n Any)] # 
Instance details

Defined in Diagrams.Backend.Rasterific.CmdLine

type MainOpts [(QDiagram Rasterific V2 n Any, GifDelay)] # 
Instance details

Defined in Diagrams.Backend.Rasterific.CmdLine

type MainOpts (Animation Rasterific V2 n) # 
Instance details

Defined in Diagrams.Backend.Rasterific.CmdLine

type MainOpts (QDiagram Rasterific V2 n Any) # 
Instance details

Defined in Diagrams.Backend.Rasterific.CmdLine

Orphan instances

ToResult [(QDiagram Rasterific V2 n Any, GifDelay)] Source #

An animated GIF can be a result.

Instance details

Associated Types

type Args [(QDiagram Rasterific V2 n Any, GifDelay)] :: * #

type ResultOf [(QDiagram Rasterific V2 n Any, GifDelay)] :: * #

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

Associated Types

type MainOpts [(String, QDiagram Rasterific V2 n Any)] :: * #

TypeableFloat n => Mainable [(QDiagram Rasterific V2 n Any, GifDelay)] Source # 
Instance details

Associated Types

type MainOpts [(QDiagram Rasterific V2 n Any, GifDelay)] :: * #

TypeableFloat n => Mainable (Animation Rasterific V2 n) Source # 
Instance details

Associated Types

type MainOpts (Animation Rasterific V2 n) :: * #

TypeableFloat n => Mainable (QDiagram Rasterific V2 n Any) Source # 
Instance details

Associated Types

type MainOpts (QDiagram Rasterific V2 n Any) :: * #