diagrams-pgf-1.4: PGF backend for diagrams drawing EDSL.

Copyright(c) 2015 Christopher Chalmers
LicenseBSD-style (see LICENSE)
Maintainerdiagrams-discuss@googlegroups.com
Safe HaskellNone
LanguageHaskell2010

Diagrams.Backend.PGF.Render

Contents

Description

This is an internal module exposeing internals for rendering a diagram. This is for advanced use only. PGF has enought for general use.

Synopsis

Documentation

data PGF Source #

This data declaration is simply used as a token to distinguish this rendering engine.

Constructors

PGF 

Instances

Show PGF Source # 

Methods

showsPrec :: Int -> PGF -> ShowS #

show :: PGF -> String #

showList :: [PGF] -> ShowS #

TypeableFloat n => Backend PGF V2 n Source # 

Associated Types

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

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

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

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

Does not support full alignment. Text is not escaped.

Methods

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

TypeableFloat n => Renderable (Hbox n) PGF Source # 

Methods

render :: PGF -> Hbox n -> Render PGF (V (Hbox n)) (N (Hbox n)) #

RealFloat n => Renderable (DImage n Embedded) PGF Source #

Supported: ImageRGB8. (Other types from DynamicImage will error)

Methods

render :: PGF -> DImage n Embedded -> Render PGF (V (DImage n Embedded)) (N (DImage n Embedded)) #

RealFloat n => Renderable (DImage n External) PGF Source #

Supported: .pdf, .jpg, .png.

Methods

render :: PGF -> DImage n External -> Render PGF (V (DImage n External)) (N (DImage n External)) #

TypeableFloat n => Renderable (Path V2 n) PGF Source # 

Methods

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

Monoid (Render PGF V2 n) Source # 

Methods

mempty :: Render PGF V2 n #

mappend :: Render PGF V2 n -> Render PGF V2 n -> Render PGF V2 n #

mconcat :: [Render PGF V2 n] -> Render PGF V2 n #

Fractional n => Default (Options PGF V2 n) Source # 

Methods

def :: Options PGF V2 n #

Hashable n => Hashable (Options PGF V2 n) Source # 

Methods

hashWithSalt :: Int -> Options PGF V2 n -> Int #

hash :: Options PGF V2 n -> Int #

type V PGF Source # 
type V PGF = V2
type N PGF Source # 
type N PGF = Double
data Options PGF V2 Source # 
data Render PGF V2 Source # 
data Render PGF V2 = R (Render n)
type Result PGF V2 n Source # 
type Result PGF V2 n = Builder
type MainOpts [(String, QDiagram PGF V2 n Any)] # 
type MainOpts (OnlineTex (QDiagram PGF V2 n Any)) # 
type MainOpts (Surface, QDiagram PGF V2 n Any) # 
type MainOpts (Surface, OnlineTex (QDiagram PGF V2 n Any)) # 
type MainOpts (QDiagram PGF V2 n Any) # 

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

Backend-specific rendering options.

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

An intermediate representation used for rendering primitives. (Typically, this will be some sort of monad, but it need not be.) The Renderable class guarantees that a backend will be able to convert primitives into this type; how these rendered primitives are combined into an ultimate Result is completely up to the backend.

Lenses

surface :: Lens' (Options PGF V2 n) Surface Source #

Lens onto the surface used to render.

sizeSpec :: Lens' (Options PGF V2 n) (SizeSpec V2 n) Source #

Lens onto the SizeSpec2D.

readable :: Lens' (Options PGF V2 n) Bool Source #

Lens onto whether the lines of the TeX output are indented.

standalone :: Lens' (Options PGF V2 n) Bool Source #

Lens onto whether a standalone TeX document should be produced.

Utilities

escapeString :: String -> String Source #

Escapes some common characters in a string. Note that this does not mean the string can't create an error, it mearly escapes common characters.