diagrams-lib-1.3.1.0: Embedded domain-specific language for declarative graphics

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

Diagrams.Backend.CmdLine

Contents

Description

Convenient creation of command-line-driven executables for rendering diagrams. This module provides a general framework and default behaviors for parsing command-line arguments, records for diagram creation options in various forms, and classes and instances for a unified entry point to command-line-driven diagram creation executables.

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

Synopsis

Options

Standard options

data DiagramOpts Source

Standard options most diagrams are likely to have.

Constructors

DiagramOpts 

Fields

_width :: Maybe Int

Final output width of diagram.

_height :: Maybe Int

Final output height of diagram.

_output :: FilePath

Output file path, format is typically chosen by extension.

diagramOpts :: Parser DiagramOpts Source

Command line parser for DiagramOpts. Width is option --width or -w. Height is option --height or -h (note we change help to be -? due to this). Output is option --output or -o.

Multi-diagram options

data DiagramMultiOpts Source

Extra options for a program that can offer a choice between multiple diagrams.

Constructors

DiagramMultiOpts 

Fields

_selection :: Maybe String

Selected diagram to render.

_list :: Bool

Flag to indicate that a list of available diagrams should be printed to standard out.

diagramMultiOpts :: Parser DiagramMultiOpts Source

Command line parser for DiagramMultiOpts. Selection is option --selection or -S. List is --list or -L.

Animation options

data DiagramAnimOpts Source

Extra options for animations.

Constructors

DiagramAnimOpts 

Fields

_fpu :: Double

Number of frames per unit time to generate for the animation.

diagramAnimOpts :: Parser DiagramAnimOpts Source

Command line parser for DiagramAnimOpts Frames per unit is --fpu or -f.

Loop options

data DiagramLoopOpts Source

Extra options for command-line looping.

Constructors

DiagramLoopOpts 

Fields

_loop :: Bool

Flag to indicate that the program should loop creation.

_src :: Maybe FilePath

File path for the source file to recompile.

_interval :: Int

Interval in seconds at which to check for recompilation.

diagramLoopOpts :: Parser DiagramLoopOpts Source

CommandLine parser for DiagramLoopOpts Loop is --loop or -l. Source is --src or -s. Interval is -i defaulting to one second.

Parsing

class Parseable a where Source

Parseable instances give a command line parser for a type. If a custom parser for a common type is wanted a newtype wrapper could be used to make a new Parseable instance. Notice that we do not want as many instances as Read because we want to limit ourselves to things that make sense to parse from the command line.

Methods

parser :: Parser a Source

Instances

Parseable Double Source

Parse Double according to its Read instance.

Parseable Int Source

Parse Int according to its Read instance.

Parseable String Source

Parse a string by just accepting the given string.

Parseable () Source

This instance is needed to signal the end of a chain of nested tuples, it always just results in the unit value without consuming anything.

Parseable DiagramOpts Source

Parse DiagramOpts using the diagramOpts parser.

Parseable DiagramMultiOpts Source

Parse DiagramMultiOpts using the diagramMultiOpts parser.

Parseable DiagramAnimOpts Source

Parse DiagramAnimOpts using the diagramAnimOpts parser.

Parseable DiagramLoopOpts Source

Parse DiagramLoopOpts using the diagramLoopOpts parser.

Parseable (Colour Double) Source

Parse Colour Double as either a named color from Data.Colour.Names or a hexadecimal color.

Parseable (AlphaColour Double) Source

Parse AlphaColour Double as either a named color from Data.Colour.Names or a hexadecimal color.

(Parseable a, Parseable b) => Parseable (a, b) Source

Allow Parseable things to be combined.

(Parseable a, Parseable b, Parseable c) => Parseable (a, b, c) Source

Triples of Parsebales should also be Parseable.

(Parseable a, Parseable b, Parseable c, Parseable d) => Parseable (a, b, c, d) Source 

readHexColor :: (Applicative m, Monad m) => String -> m (AlphaColour Double) Source

Parses a hexadecimal color. The string can start with "0x" or "#" or just be a string of hexadecimal values. If four or three digits are given each digit is repeated to form a full 24 or 32 bit color. For example, "0xfc4" is the same as "0xffcc44". When eight or six digits are given each pair of digits is a color or alpha channel with the order being red, green, blue, alpha.

Command-line programs (Mainable)

Arguments, rendering, and entry point

class Mainable d where Source

This class represents the various ways we want to support diagram creation from the command line. It has the right instances to select between creating single static diagrams, multiple static diagrams, static animations, and functions that produce diagrams as long as the arguments are Parseable.

Backends are expected to create Mainable instances for the types that are suitable for generating output in the backend's format. For instance, Postscript can handle single diagrams, pages of diagrams, animations as separate files, and association lists. This implies instances for Diagram Postscript R2, [Diagram Postscript R2], Animation Postscript R2, and [(String,Diagram Postscript R2)]. We can consider these as the base cases for the function instance.

The associated type MainOpts describes the options which need to be parsed from the command-line and passed to mainRender.

Minimal complete definition

mainRender

Associated Types

type MainOpts d :: * Source

Associated type that describes the options which need to be parsed from the command-line and passed to mainRender.

Methods

mainArgs :: Parseable (MainOpts d) => d -> IO (MainOpts d) Source

This method invokes the command-line parser resulting in an options value or ending the program with an error or help message. Typically the default instance will work. If a different help message or parsing behavior is desired a new implementation is appropriate.

Note the d argument should only be needed to fix the type d. Its value should not be relied on as a parameter.

mainRender :: MainOpts d -> d -> IO () Source

Backend specific work of rendering with the given options and mainable value is done here. All backend instances should implement this method.

mainWith :: Parseable (MainOpts d) => d -> IO () Source

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.

Instances

Mainable d => Mainable (IO d) Source

With this instance we can perform IO to produce something Mainable before rendering.

(Parseable (Args (a -> d)), ToResult d, Mainable (ResultOf d)) => Mainable (a -> d) Source

This instance allows functions resulting in something that is Mainable to be Mainable. It takes a parse of collected arguments and applies them to the given function producing the Mainable result.

General currying

class ToResult d where Source

This class allows us to abstract over functions that take some arguments and produce a final value. When some d is an instance of ToResult we get a type Args d that is a type of all the arguments at once, and a type ResultOf d that is the type of the final result from some base case instance.

Associated Types

type Args d :: * Source

type ResultOf d :: * Source

Methods

toResult :: d -> Args d -> ResultOf d Source

Instances

ToResult [(String, QDiagram b v n Any)] Source

A list of named diagrams can give the multi-diagram interface.

ToResult [QDiagram b v n Any] Source

A list of diagrams can produce pages.

ToResult d => ToResult (IO d) Source

Diagrams that require IO to build are a base case.

ToResult d => ToResult (a -> d) Source

An instance for a function that, given some a, can produce a d that is also an instance of ToResult. For this to work we need both the argument a and all the arguments that d will need. Producing the result is simply applying the argument to the producer and passing the remaining arguments to the produced producer.

ToResult (Animation b v n) Source

An animation is another suitable base case.

ToResult (QDiagram b v n Any) Source

A diagram can always produce a diagram when given () as an argument. This is our base case.

helper functions for implementing mainRender

defaultAnimMainRender Source

Arguments

:: (opts -> QDiagram b v n Any -> IO ()) 
-> Lens' opts FilePath

A lens into the output path.

-> (opts, DiagramAnimOpts) 
-> Animation b v n 
-> IO () 

defaultAnimMainRender is an implementation of mainRender which renders an animation as numbered frames, named by extending the given output file name by consecutive integers. For example if the given output file name is foo/blah.ext, the frames will be saved in foo/blah001.ext, foo/blah002.ext, 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 from DiagramAnimOpts can be used to control how many frames will be output for each second (unit time) of animation.

This function requires a lens into the structure that the particular backend uses for it's diagram base case. If MainOpts (QDiagram b v n Any) ~ DiagramOpts then this lens will simply be output. For a backend supporting looping it will most likely be _1 . output. This lens is required because the implementation works by modifying the output field and running the base mainRender. Typically a backend can write its Animation B V instance as

  instance Mainable (Animation B V) where
      type MainOpts (Animation B V) = (DiagramOpts, DiagramAnimOpts)
      mainRender = defaultAnimMainRender output
  

We do not provide this instance in general so that backends can choose to opt-in to this form or provide a different instance that makes more sense.

defaultMultiMainRender :: Mainable d => (MainOpts d, DiagramMultiOpts) -> [(String, d)] -> IO () Source

defaultMultiMainRender is an implementation of mainRender where 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.

Typically a backend can write its [(String,QDiagram b v n Any)] instance as

  instance Mainable [(String,QDiagram b v n Any)] where
      type MainOpts [(String,QDiagram b v n Any)] = (DiagramOpts, DiagramMultiOpts)
      mainRender = defaultMultiMainRender
  

We do not provide this instance in general so that backends can choose to opt-in to this form or provide a different instance that makes more sense.