diagrams-pgf-0.1.0.3: 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

Contents

Description

A full-featured PGF backend for diagrams producing PGF code suitable for LaTeX, ConTeXt or plain TeX consumption.

To invoke the PGF backend, you have a number of options.

The Surface provides the necessary information for rendering PGF code and building a PDF using "texrunner". See Surface for more info.

Synopsis

Rendering token & options

data PGF Source

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

Constructors

PGF 

Instances

Show PGF Source 
TypeableFloat n => Backend PGF V2 n Source 
TypeableFloat n => Renderable (Text n) PGF Source

Does not support full alignment. Text is not escaped.

TypeableFloat n => Renderable (Hbox n) PGF Source 
RealFloat n => Renderable (DImage n Embedded) PGF Source

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

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

Supported: .pdf, .jpg, .png.

TypeableFloat n => Renderable (Path V2 n) PGF Source 
Monoid (Render PGF V2 n) Source 
Fractional n => Default (Options PGF V2 n) Source 
Hashable n => Hashable (Options PGF V2 n) Source 
type V PGF = V2 
type N PGF = Double 
data Options PGF V2 = PGFOptions {} Source 
data Render PGF V2 = R (Render n) Source 
type Result PGF V2 n = Builder Source 
type MainOpts [(String, QDiagram PGF V2 n Any)] = (MainOpts (QDiagram PGF V2 n Any), DiagramMultiOpts) 
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) 

type B = PGF Source

Rendering functions

renderPGF Source

Arguments

:: (TypeableFloat n, Monoid' m) 
=> FilePath

path to output

-> SizeSpec V2 n

size of output

-> QDiagram PGF V2 n m

Diagram to render

-> IO () 

Render a pgf diagram and write it to the given filepath. Same as renderPGF' but uses the default options.

renderPGF' :: (TypeableFloat n, Monoid' m) => FilePath -> Options PGF V2 n -> QDiagram PGF V2 n m -> IO () Source

Render a pgf diagram and write it to the given filepath. If the file has the extension .pdf, a PDF is generated in a temporary directory using options from the given surface, otherwise, the tex output is saved using the surface's TexFormat.

renderPGFSurf Source

Arguments

:: (TypeableFloat n, Monoid' m) 
=> FilePath

path to output

-> SizeSpec V2 n

size of output

-> Surface

surface to render with

-> QDiagram PGF V2 n m

diagram to render

-> IO () 

Render a pgf diagram and write it to the given filepath. Same as renderPGF but takes a Surface.

Options

Options for changing how the diagram is rendered. Options PGF is an instance of Default:

def = PGFOptions {
  _surface    = latexSurface
  _sizeSpec   = absolute
  _readable   = True
  _standalone = False
  }

You can edit the default options using lenses.

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

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

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

Lens onto the SizeSpec2D.

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

Lens onto the surface used to render.

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

Lens onto whether a standalone TeX document should be produced.

Surfaces

These surfaces should be suitable for basic diagrams. For more complicated options see Surface.

data Surface Source

Instances

surfOnlineTex :: Surface -> OnlineTex a -> a Source

Get the result of an OnlineTex using the given surface.

Predefined surfaces

latexSurface :: Surface Source

Default surface for latex files by calling pdflatex.

Sample output

command: pdflatex

% preamble
documentclass{article}
usepackage{pgfcore}
pagenumbering{gobble}

% pageSize
pdfpagewidth=100bp
pdfpageheight=80bp
textheight=80bp
pdfhorigin=-76.6bp
pdfvorigin=-52.8bp

% beginDoc
begin{document}

<Latex pgf code>

% endDoc
end{document}

contextSurface :: Surface Source

Default surface for latex files by calling pdflatex.

Sample output

command: context --pipe --once

% preamble
usemodule[pgf]
setuppagenumbering[location=]

% pageSize
definepapersize[diagram][width=100bp,height=80bp]
setuppapersize[diagram][diagram]
setuplayout
  [ topspace=0bp
  , backspace=0bp
  , header=0bp
  , footer=0bp
  , width=100bp
  , height=80bp
  ]

% beginDoc
starttext

<Context pgf code>

% endDoc
stoptext

plaintexSurface :: Surface Source

Default surface for latex files by calling pdflatex.

Sample output

command: pdftex

% preamble
input eplain
beginpackages
usepackage{color}
endpackages
input pgfcore
deffrac2{{begingroup 2}}nopagenumbers

% pageSize
pdfpagewidth=100bp
pdfpageheight=80bp
pdfhorigin=-20bp
pdfvorigin=0bp

% beginDoc


pgf code

% endDoc
bye

Lenses

command :: Lens' Surface String Source

System command to call for rendering PDFs for OnlineTex.

arguments :: Lens' Surface [String] Source

List of arguments for the command.

preamble :: Lens' Surface String Source

Preamble for the tex document. This should at least import pgfcore.

Online TeX

By using OnlineTex, diagrams is able to query tex for sizes of hboxs and give them the corresponding envelopes. These can then be used as any other diagram with the correct size.

Online diagrams use the Surface to run tex in online mode and get feedback for hbox sizes. To run it you can use renderOnlinePGF, renderOnlinePGF' or onlineMain from CmdLine.

See https://github.com/diagrams/diagrams-pgf/tree/master/examples for examples.

data OnlineTex a :: * -> *

Type for dealing with Tex's pipping interface, the current streams are availble though the MonadReader instance.

renderOnlinePGF :: (TypeableFloat n, Monoid' m) => FilePath -> SizeSpec V2 n -> OnlineTex (QDiagram PGF V2 n m) -> IO () Source

Render an online PGF diagram and save it. Same as renderOnlinePGF' using default options.

renderOnlinePGF' :: (TypeableFloat n, Monoid' m) => FilePath -> Options PGF V2 n -> OnlineTex (QDiagram PGF V2 n m) -> IO () Source

Same as renderOnlinePDF but takes Options PGF.

Hbox

data Hbox n Source

Primitive for placing raw Tex commands in a hbox.

hboxOnline :: (TypeableFloat n, Renderable (Hbox n) b) => String -> OnlineTex (QDiagram b V2 n Any) Source

Hbox with bounding box envelope.

hboxPoint :: (OrderedField n, Typeable n, Renderable (Hbox n) b) => String -> QDiagram b V2 n Any Source

Raw Tex commands in a hbox with no envelope. Transformations are applied normally. This primitive ignores FontSize.

hboxSurf :: (TypeableFloat n, Renderable (Hbox n) b) => Surface -> String -> QDiagram b V2 n Any Source

Hbox with bounding box envelope. Note that each box requires a call to Tex. For multiple boxes consider using onlineHbox to get multiple boxes from a single call. (uses unsafePerformIO)