diagrams-braille-0.1.1: Braille diagrams with plain text
Safe HaskellNone
LanguageHaskell2010

Diagrams.Backend.Braille.CmdLine

Description

Convenient creation of command-line-driven executables for rendering diagrams to Braille.

  • 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 suitable final result (any of arguments to the above types) and Parseable arguments.

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

defaultMain :: Diagram B -> IO () Source #

mainWith specialised to Diagram Rasterific.

multiMain :: [(String, Diagram B)] -> IO () Source #

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

Backend tokens

data Braille Source #

Instances

Instances details
Eq Braille Source # 
Instance details

Defined in Diagrams.Backend.Braille

Methods

(==) :: Braille -> Braille -> Bool #

(/=) :: Braille -> Braille -> Bool #

Ord Braille Source # 
Instance details

Defined in Diagrams.Backend.Braille

Read Braille Source # 
Instance details

Defined in Diagrams.Backend.Braille

Show Braille Source # 
Instance details

Defined in Diagrams.Backend.Braille

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

Defined in Diagrams.Backend.Braille

Associated Types

data Render Braille V2 n #

type Result Braille V2 n #

data Options Braille V2 n #

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

Defined in Diagrams.Backend.Braille.CmdLine

Associated Types

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

Methods

mainArgs :: Parseable (MainOpts [(String, QDiagram B V2 n Any)]) => proxy [(String, QDiagram B V2 n Any)] -> IO (MainOpts [(String, QDiagram B V2 n Any)]) #

mainRender :: MainOpts [(String, QDiagram B V2 n Any)] -> [(String, QDiagram B V2 n Any)] -> IO () #

mainWith :: [(String, QDiagram B V2 n Any)] -> IO () #

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

Defined in Diagrams.Backend.Braille

Methods

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

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

Defined in Diagrams.Backend.Braille

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

Defined in Diagrams.Backend.Braille

Methods

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

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

Defined in Diagrams.Backend.Braille

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

Defined in Diagrams.Backend.Braille

Semigroup (Render Braille V2 n) Source # 
Instance details

Defined in Diagrams.Backend.Braille

Monoid (Render Braille V2 n) Source # 
Instance details

Defined in Diagrams.Backend.Braille

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

Defined in Diagrams.Backend.Braille

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

Defined in Diagrams.Backend.Braille.CmdLine

Associated Types

type MainOpts (QDiagram B V2 n Any) #

type V Braille Source # 
Instance details

Defined in Diagrams.Backend.Braille

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

Defined in Diagrams.Backend.Braille

data Options Braille V2 n Source # 
Instance details

Defined in Diagrams.Backend.Braille

newtype Render Braille V2 n Source # 
Instance details

Defined in Diagrams.Backend.Braille

newtype Render Braille V2 n = R (RenderM n ())
type Result Braille V2 n Source # 
Instance details

Defined in Diagrams.Backend.Braille

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

Defined in Diagrams.Backend.Braille.CmdLine

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

Defined in Diagrams.Backend.Braille.CmdLine

type B = Braille Source #

Orphan instances

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

Associated Types

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

Methods

mainArgs :: Parseable (MainOpts [(String, QDiagram B V2 n Any)]) => proxy [(String, QDiagram B V2 n Any)] -> IO (MainOpts [(String, QDiagram B V2 n Any)]) #

mainRender :: MainOpts [(String, QDiagram B V2 n Any)] -> [(String, QDiagram B V2 n Any)] -> IO () #

mainWith :: [(String, QDiagram B V2 n Any)] -> IO () #

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

Associated Types

type MainOpts (QDiagram B V2 n Any) #