diagrams-braille-0.1.0.2: Braille diagrams with plain text

Safe HaskellNone
LanguageHaskell2010

Diagrams.Backend.Braille

Contents

Description

A rendering backend for Braille diagrams using Rasterific, implemented natively in Haskell (making it easy to use on any platform).

To invoke the Braille backend, you have three options.

  • You can use the Diagrams.Backend.Braille.CmdLine module to create standalone executables which output images when invoked.
  • You can use the renderBraille function provided by this module, which gives you more flexible programmatic control over when and how images are output (making it easy to, for example, write a single program that outputs multiple images, or one that outputs images dynamically based on user input, and so on).
  • For the most flexibility (e.g. if you want access to the resulting Braille value directly in memory without writing it to disk), you can manually invoke the renderDia method from the Backend instance for Braille. In particular, renderDia has the generic type
renderDia :: b -> Options b v n -> QDiagram b v n m -> Result b v n

(omitting a few type class constraints). b represents the backend type, v the vector space, n the numeric field, and m the type of monoidal query annotations on the diagram. Options and Result are associated data and type families, respectively, which yield the type of option records and rendering results specific to any particular backend. For b ~ Braille, v ~ V2, and n ~ n, we have

data Options Braille V2 n = BrailleOptions
       { _size      :: SizeSpec2D n -- ^ The requested size of the output
       }
type family Result Braille V2 n = String

So the type of renderDia resolves to

renderDia :: Braille -> Options Braille V2 n -> QDiagram Braille V2 n m -> String

which you could call like renderDia Braille (BrailleOptions (mkWidth 80)) myDiagram.

Synopsis

Braille backend

data Braille Source #

Constructors

Braille 
Instances
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)] # 
Instance details

Defined in Diagrams.Backend.Braille.CmdLine

Associated Types

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

Methods

mainArgs :: [(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)) #

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) # 
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

data Render Braille V2 n Source # 
Instance details

Defined in Diagrams.Backend.Braille

data 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)] # 
Instance details

Defined in Diagrams.Backend.Braille.CmdLine

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

Defined in Diagrams.Backend.Braille.CmdLine

type B = Braille Source #

data family Options b (v :: * -> *) n :: * #

Backend-specific rendering options.

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

Defined in Diagrams.Backend.Braille

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

Defined in Diagrams.Backend.Braille

data Options NullBackend v n 
Instance details

Defined in Diagrams.Core.Types

data Options Braille V2 n # 
Instance details

Defined in Diagrams.Backend.Braille

Rendering

renderBraille :: TypeableFloat n => FilePath -> SizeSpec V2 n -> QDiagram Braille V2 n Any -> IO () Source #

Render a Braille diagram to a file with the given size. The format is determined by the extension (.png, .tif, .bmp, .jpg and .pdf supported.

size :: (V a ~ v, N a ~ n, Enveloped a, HasBasis v) => a -> v n #

The smallest positive axis-parallel vector that bounds the envelope of an object.