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

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

Diagrams.Backend.PGF.Hbox

Contents

Description

A hbox a primitive Tex box, typically used for holding text and formulas but can hold anything. This module provides functions for retrieving the dimensions of these boxes to give diagrams the correct envelopes.

Synopsis

Documentation

data Hbox n Source #

Primitive for placing raw Tex commands in a hbox.

Constructors

Hbox (Transformation V2 n) String 
Instances
Fractional n => Transformable (Hbox n) Source # 
Instance details

Defined in Diagrams.Backend.PGF.Hbox

Methods

transform :: Transformation (V (Hbox n)) (N (Hbox n)) -> Hbox n -> Hbox n #

Fractional n => Renderable (Hbox n) NullBackend Source # 
Instance details

Defined in Diagrams.Backend.PGF.Hbox

Methods

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

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

Defined in Diagrams.Backend.PGF.Render

Methods

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

type V (Hbox n) Source # 
Instance details

Defined in Diagrams.Backend.PGF.Hbox

type V (Hbox n) = V2
type N (Hbox n) Source # 
Instance details

Defined in Diagrams.Backend.PGF.Hbox

type N (Hbox n) = n

Enveloped diagrams

The dimensions of a hbox can be recovered by calling Tex. The resulting envelope has its origin at the baseline of the text.

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

Hbox with bounding box envelope.

Non-Online version

These versions bypass OnlineTex by just running a whole tex program just to get the size of a single hbox. This is not recommended but because it is slow, but can be convenient if you only need one or two hbox sizes.

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 hboxOnline to get multiple boxes from a single call. (uses unsafePerformIO)

hboxSurfIO :: (TypeableFloat n, Renderable (Hbox n) b) => Surface -> String -> IO (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 hboxOnline to get multiple boxes from a single call.

Point envelope diagrams

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.