| Maintainer | diagrams-discuss@googlegroups.com | 
|---|---|
| Safe Haskell | None | 
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.
- data DiagramOpts = DiagramOpts {}
- diagramOpts :: Parser DiagramOpts
- width :: Lens' DiagramOpts (Maybe Int)
- height :: Lens' DiagramOpts (Maybe Int)
- output :: Lens' DiagramOpts FilePath
- data  DiagramMultiOpts  = DiagramMultiOpts {- _selection :: Maybe String
- _list :: Bool
 
- diagramMultiOpts :: Parser DiagramMultiOpts
- selection :: Lens' DiagramMultiOpts (Maybe String)
- list :: Lens' DiagramMultiOpts Bool
- data DiagramAnimOpts = DiagramAnimOpts {}
- diagramAnimOpts :: Parser DiagramAnimOpts
- fpu :: Iso' DiagramAnimOpts Double
- data DiagramLoopOpts = DiagramLoopOpts {}
- diagramLoopOpts :: Parser DiagramLoopOpts
- loop :: Lens' DiagramLoopOpts Bool
- src :: Lens' DiagramLoopOpts (Maybe FilePath)
- interval :: Lens' DiagramLoopOpts Int
- class Parseable a where
- readHexColor :: String -> Maybe (AlphaColour Double)
- class Mainable d where
- class ToResult d where
- defaultAnimMainRender :: Mainable (Diagram b v) => Lens' (MainOpts (Diagram b v)) FilePath -> (MainOpts (Diagram b v), DiagramAnimOpts) -> Animation b v -> IO ()
- defaultMultiMainRender :: Mainable d => (MainOpts d, DiagramMultiOpts) -> [(String, d)] -> IO ()
Options
Standard options
data DiagramOpts Source
Standard options most diagrams are likely to have.
Constructors
| DiagramOpts | |
Instances
| Data DiagramOpts | |
| Show DiagramOpts | |
| Typeable DiagramOpts | |
| Parseable DiagramOpts | Parse  | 
diagramOpts :: Parser DiagramOptsSource
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 
 | |
Instances
| Data DiagramMultiOpts | |
| Show DiagramMultiOpts | |
| Typeable DiagramMultiOpts | |
| Parseable DiagramMultiOpts | Parse  | 
diagramMultiOpts :: Parser DiagramMultiOptsSource
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 | |
Instances
| Data DiagramAnimOpts | |
| Show DiagramAnimOpts | |
| Typeable DiagramAnimOpts | |
| Parseable DiagramAnimOpts | Parse  | 
diagramAnimOpts :: Parser DiagramAnimOptsSource
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 | |
Instances
| Parseable DiagramLoopOpts | Parse  | 
diagramLoopOpts :: Parser DiagramLoopOptsSource
CommandLine parser for DiagramLoopOpts
   Loop is --loop or -l.
   Source is --src or -s.
   Interval is -i defaulting to one second.
Parsing
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.
Instances
| Parseable Double | |
| Parseable Int | |
| Parseable String | Parse a string by just accepting the given string. | 
| Parseable () | 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 | Parse  | 
| Parseable DiagramMultiOpts | Parse  | 
| Parseable DiagramAnimOpts | Parse  | 
| Parseable DiagramLoopOpts | Parse  | 
| Parseable (Colour Double) | Parse  | 
| Parseable (AlphaColour Double) | Parse  | 
| (Parseable a, Parseable b) => Parseable (a, b) | Allow  | 
readHexColor :: String -> Maybe (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
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.
Associated Types
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) | With this instance we can perform IO to produce something
    | 
| (Parseable (Args (a -> d)), ToResult d, Mainable (ResultOf d)) => Mainable (a -> d) | This instance allows functions resulting in something that is  | 
General currying
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 dResultOf d
Instances
| ToResult [(String, Diagram b v)] | A list of named diagrams can give the multi-diagram interface. | 
| ToResult [Diagram b v] | A list of diagrams can produce pages. | 
| ToResult d => ToResult (IO d) | Diagrams that require IO to build are a base case. | 
| ToResult d => ToResult (a -> d) | An instance for a function that, given some  | 
| ToResult (Diagram b v) | A diagram can always produce a diagram when given  | 
| ToResult (Animation b v) | An animation is another suitable base case. | 
Default mainRender implementations
Arguments
| :: Mainable (Diagram b v) | |
| => Lens' (MainOpts (Diagram b v)) FilePath | A lens into the output path. | 
| -> (MainOpts (Diagram b v), DiagramAnimOpts) | |
| -> Animation b v | |
| -> 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 (Diagram b v) ~ 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,Diagram B V)] instance as
   instance Mainable [(String,Diagram B V)] where
       type MainOpts [(String,Diagram B V)] = (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.