diagrams-braille-0.1.0.1: 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 # 

Methods

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

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

Ord Braille Source # 
Read Braille Source # 
Show Braille Source # 
TypeableFloat n => Backend Braille V2 n Source # 

Associated Types

data Render Braille (V2 :: * -> *) n :: * #

type Result Braille (V2 :: * -> *) n :: * #

data Options Braille (V2 :: * -> *) n :: * #

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

Methods

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

TypeableFloat n => Renderable (DImage n Embedded) Braille Source # 
TypeableFloat n => Renderable (Path V2 n) Braille Source # 

Methods

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

Show n => Show (Options Braille V2 n) Source # 
Monoid (Render Braille V2 n) Source # 
Hashable n => Hashable (Options Braille V2 n) Source # 
type V Braille Source # 
type V Braille = V2
type N Braille Source # 
data Options Braille V2 Source # 
data Render Braille V2 Source # 
data Render Braille V2 = R (RenderM n ())
type Result Braille V2 n Source # 
type MainOpts [(String, QDiagram B V2 n Any)] # 
type MainOpts (QDiagram B V2 n Any) # 

type B = Braille Source #

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

Backend-specific rendering options.

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.