HPDF-1.5.0: Generation of PDF documents

Copyright(c) 2006-2016 alpheccar.org
LicenseBSD-style
Maintainermisc@NOSPAMalpheccar.org
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Graphics.PDF.Typesetting

Contents

Description

Experimental typesetting. It is a work in progress

Synopsis

Types

Boxes

class Box a where Source #

A box is an object with dimensions and used in the typesetting process

Minimal complete definition

boxWidth, boxHeight, boxDescent

Methods

boxWidth Source #

Arguments

:: a

Box

-> PDFFloat

Width of the box

Box width

boxHeight :: a -> PDFFloat Source #

Box height

boxDescent :: a -> PDFFloat Source #

Distance between box bottom and box baseline

boxAscent :: a -> PDFFloat Source #

Distance between box top and box baseline

class DisplayableBox a where Source #

A box that can be displayed

Methods

strokeBox Source #

Arguments

:: a

The box

-> PDFFloat

Horizontal position

-> PDFFloat

Vertical position (top of the box and NOT baseline)

-> Draw () 

Draw a box

Instances
ParagraphStyle ps s => DisplayableBox (VBox ps s) Source # 
Instance details

Defined in Graphics.PDF.Typesetting.Layout

Methods

strokeBox :: VBox ps s -> PDFFloat -> PDFFloat -> Draw () Source #

data Letter s Source #

A letter which can be anything. Sizes are widths and for glue the dilation and compression factors For the generic letter, height and descent are also provided

Constructors

Letter BoxDimension !AnyBox !(Maybe s)

Any box as a letter

Glue !PDFFloat !PDFFloat !PDFFloat !(Maybe s)

A glue with style to know if it is part of the same sentence

FlaggedPenalty !PDFFloat !Int !s

Hyphen point

Penalty !Int

Penalty

AGlyph !s !GlyphCode !PDFFloat

A glyph

Kern !PDFFloat !(Maybe s)

A kern : non dilatable and non breakable glue

Instances
Show (Letter s) Source # 
Instance details

Defined in Graphics.PDF.Typesetting.Breaking

Methods

showsPrec :: Int -> Letter s -> ShowS #

show :: Letter s -> String #

showList :: [Letter s] -> ShowS #

MonadWriter [Letter s] (Para s) Source # 
Instance details

Defined in Graphics.PDF.Typesetting

Methods

writer :: (a, [Letter s]) -> Para s a #

tell :: [Letter s] -> Para s () #

listen :: Para s a -> Para s (a, [Letter s]) #

pass :: Para s (a, [Letter s] -> [Letter s]) -> Para s a #

type BoxDimension = (PDFFloat, PDFFloat, PDFFloat) Source #

Dimension of a box : width, height and descent

Styles

class ComparableStyle a => Style a where Source #

Style of text (sentences and words). Minimum definition textStyle

Minimal complete definition

textStyle

Methods

sentenceStyle Source #

Arguments

:: a

The style

-> Maybe (Rectangle -> Draw b -> Draw ())

Function receiving the bounding rectangle and the command for drawing the sentence

Modify the look of a sentence (sequence of words using the same style on a line)

wordStyle Source #

Arguments

:: a

The style

-> Maybe (Rectangle -> StyleFunction -> Draw b -> Draw ())

Word styling function

textStyle :: a -> TextStyle Source #

updateStyle :: a -> a Source #

A style may contain data changed from word to word

styleHeight :: a -> PDFFloat Source #

A style may change the height of words

Default implementation
styleHeight = getHeight . textFont . textStyle

styleDescent :: a -> PDFFloat Source #

A style may change the descent of lines

Default implementation
styleDescent = getDescent . textFont . textStyle

data TextStyle Source #

Text style used by PDF operators

Constructors

TextStyle 

Fields

Instances
Eq TextStyle Source # 
Instance details

Defined in Graphics.PDF.Typesetting.Box

data StyleFunction Source #

What kind of style drawing function is required for a word when word styling is enabled

Constructors

DrawWord

Must style a word

DrawGlue

Must style a glue

class (ComparableStyle a, Style s) => ParagraphStyle a s | a -> s where Source #

Paragraph style

Minimal complete definition

Nothing

Methods

lineWidth Source #

Arguments

:: a

The style

-> PDFFloat

Width of the text area used by the typesetting algorithm

-> Int

Line number

-> PDFFloat

Line width

Width of the line of the paragraph

linePosition Source #

Arguments

:: a

The style

-> PDFFloat

Width of the text area used by the typesetting algorithm

-> Int

Line number

-> PDFFloat

Horizontal offset from the left edge of the text area

Horizontal shift of the line position relatively to the left egde of the paragraph bounding box

interline Source #

Arguments

:: a

The style

-> Maybe (Rectangle -> Draw ())

Function used to style interline glues

How to style the interline glues added in a paragraph by the line breaking algorithm

paragraphChange Source #

Arguments

:: a

The style

-> Int

Line offset different from 0 when a paragraph has been broken

-> [Letter s]

List of letters in the paragraph

-> (a, [Letter s])

Update style and list of letters

Change the content of a paragraph before the line breaking algorithm is run. It may also change the style

paragraphStyle Source #

Arguments

:: a

The style

-> Maybe (Rectangle -> Draw b -> Draw ())

Function used to style a paragraph

Get the paragraph bounding box and the paragraph draw command to apply additional effects

class (Style s, Monad m) => MonadStyle s m | m -> s where Source #

A MonadStyle where some typesetting operators can be used

Methods

setStyle :: s -> m () Source #

Set the current text style

currentStyle :: m s Source #

Get the current text style

addBox Source #

Arguments

:: (Show a, DisplayableBox a, Box a) 
=> a 
-> PDFFloat

Width

-> PDFFloat

Height

-> PDFFloat

Descent

-> m () 

Add a box using the current mode (horizontal or vertical. The current style is always applied to the added box)

glue Source #

Arguments

:: PDFFloat

Size of glue (width or height depending on the mode)

-> PDFFloat

Dilatation factor

-> PDFFloat

Compression factor

-> m () 

Add a glue using the current style

unstyledGlue Source #

Arguments

:: PDFFloat

Size of glue (width or height depending on the mode)

-> PDFFloat

Dilatation factor

-> PDFFloat

Compression factor

-> m () 

Add a glue with no style (it is just a translation)

Instances
Style s => MonadStyle s (Para s) Source # 
Instance details

Defined in Graphics.PDF.Typesetting

Style s => MonadStyle s (TM ps s) Source # 
Instance details

Defined in Graphics.PDF.Typesetting

Methods

setStyle :: s -> TM ps s () Source #

currentStyle :: TM ps s s Source #

addBox :: (Show a, DisplayableBox a, Box a) => a -> PDFFloat -> PDFFloat -> PDFFloat -> TM ps s () Source #

glue :: PDFFloat -> PDFFloat -> PDFFloat -> TM ps s () Source #

unstyledGlue :: PDFFloat -> PDFFloat -> PDFFloat -> TM ps s () Source #

class ComparableStyle a where Source #

Used to compare two style without taking into account the style state

Methods

isSameStyleAs :: a -> a -> Bool Source #

Typesetting monads

data Para s a Source #

Instances
MonadState s (Para s) Source # 
Instance details

Defined in Graphics.PDF.Typesetting

Methods

get :: Para s s #

put :: s -> Para s () #

state :: (s -> (a, s)) -> Para s a #

Style s => MonadStyle s (Para s) Source # 
Instance details

Defined in Graphics.PDF.Typesetting

Monad (Para s) Source # 
Instance details

Defined in Graphics.PDF.Typesetting

Methods

(>>=) :: Para s a -> (a -> Para s b) -> Para s b #

(>>) :: Para s a -> Para s b -> Para s b #

return :: a -> Para s a #

fail :: String -> Para s a #

Functor (Para s) Source # 
Instance details

Defined in Graphics.PDF.Typesetting

Methods

fmap :: (a -> b) -> Para s a -> Para s b #

(<$) :: a -> Para s b -> Para s a #

Applicative (Para s) Source # 
Instance details

Defined in Graphics.PDF.Typesetting

Methods

pure :: a -> Para s a #

(<*>) :: Para s (a -> b) -> Para s a -> Para s b #

liftA2 :: (a -> b -> c) -> Para s a -> Para s b -> Para s c #

(*>) :: Para s a -> Para s b -> Para s b #

(<*) :: Para s a -> Para s b -> Para s a #

MonadWriter [Letter s] (Para s) Source # 
Instance details

Defined in Graphics.PDF.Typesetting

Methods

writer :: (a, [Letter s]) -> Para s a #

tell :: [Letter s] -> Para s () #

listen :: Para s a -> Para s (a, [Letter s]) #

pass :: Para s (a, [Letter s] -> [Letter s]) -> Para s a #

data TM ps s a Source #

Instances
Style s => MonadStyle s (TM ps s) Source # 
Instance details

Defined in Graphics.PDF.Typesetting

Methods

setStyle :: s -> TM ps s () Source #

currentStyle :: TM ps s s Source #

addBox :: (Show a, DisplayableBox a, Box a) => a -> PDFFloat -> PDFFloat -> PDFFloat -> TM ps s () Source #

glue :: PDFFloat -> PDFFloat -> PDFFloat -> TM ps s () Source #

unstyledGlue :: PDFFloat -> PDFFloat -> PDFFloat -> TM ps s () Source #

MonadWriter [VBox ps s] (TM ps s) Source # 
Instance details

Defined in Graphics.PDF.Typesetting

Methods

writer :: (a, [VBox ps s]) -> TM ps s a #

tell :: [VBox ps s] -> TM ps s () #

listen :: TM ps s a -> TM ps s (a, [VBox ps s]) #

pass :: TM ps s (a, [VBox ps s] -> [VBox ps s]) -> TM ps s a #

Monad (TM ps s) Source # 
Instance details

Defined in Graphics.PDF.Typesetting

Methods

(>>=) :: TM ps s a -> (a -> TM ps s b) -> TM ps s b #

(>>) :: TM ps s a -> TM ps s b -> TM ps s b #

return :: a -> TM ps s a #

fail :: String -> TM ps s a #

Functor (TM ps s) Source # 
Instance details

Defined in Graphics.PDF.Typesetting

Methods

fmap :: (a -> b) -> TM ps s a -> TM ps s b #

(<$) :: a -> TM ps s b -> TM ps s a #

Applicative (TM ps s) Source # 
Instance details

Defined in Graphics.PDF.Typesetting

Methods

pure :: a -> TM ps s a #

(<*>) :: TM ps s (a -> b) -> TM ps s a -> TM ps s b #

liftA2 :: (a -> b -> c) -> TM ps s a -> TM ps s b -> TM ps s c #

(*>) :: TM ps s a -> TM ps s b -> TM ps s b #

(<*) :: TM ps s a -> TM ps s b -> TM ps s a #

Containers

data VBox ps s Source #

Instances
MonadWriter [VBox ps s] (TM ps s) Source # 
Instance details

Defined in Graphics.PDF.Typesetting

Methods

writer :: (a, [VBox ps s]) -> TM ps s a #

tell :: [VBox ps s] -> TM ps s () #

listen :: TM ps s a -> TM ps s (a, [VBox ps s]) #

pass :: TM ps s (a, [VBox ps s] -> [VBox ps s]) -> TM ps s a #

Show (VBox ps s) Source # 
Instance details

Defined in Graphics.PDF.Typesetting.Layout

Methods

showsPrec :: Int -> VBox ps s -> ShowS #

show :: VBox ps s -> String #

showList :: [VBox ps s] -> ShowS #

ParagraphStyle ps s => DisplayableBox (VBox ps s) Source # 
Instance details

Defined in Graphics.PDF.Typesetting.Layout

Methods

strokeBox :: VBox ps s -> PDFFloat -> PDFFloat -> Draw () Source #

Box (VBox ps s) Source # 
Instance details

Defined in Graphics.PDF.Typesetting.Layout

data VerState s Source #

Constructors

VerState 

Fields

data Container ps s Source #

Container for vboxes (x,y,width,maxheight,height,currenty,current z, tolerance para) tolerance para means a paragraph is not started if too close from the bottom edge of the box

data Orientation Source #

Constructors

E 
W 
N 
S 
NE 
NW 
SE 
SW 

Functions

Text display

displayFormattedText Source #

Arguments

:: ParagraphStyle ps s 
=> Rectangle

Text area

-> ps

default vertical style

-> s

Default horizontal style

-> TM ps s a

Typesetting monad

-> Draw a

Draw monad

Display a formatted text in a given bounding rectangle with a given default paragraph style, a given default text style. No clipping is taking place. Drawing stop when the last line is crossing the bounding rectangle in vertical direction

Text construction operators

txt :: Style s => Text -> Para s () Source #

Add a null char nullChar :: Para () nullChar = Para . tell $ [nullLetter]

Add a text line

kern :: Style s => PDFFloat -> Para s () Source #

add a kern (space that can be dilated or compressed and on which no line breaking can occur)

addPenalty :: Int -> Para s () Source #

Add a penalty

mkLetter Source #

Arguments

:: (Show a, Box a, DisplayableBox a) 
=> BoxDimension

Dimension of the box

-> Maybe s

Text style of the box (can use t)

-> a

Box

-> Letter s 

Make a letter from any box

mkDrawBox :: Draw () -> DrawBox Source #

Make a drawing box. A box object containing a Draw value

Paragraph construction operators

forceNewLine :: Style s => Para s () Source #

For a newline and end the current paragraph

paragraph :: Style s => Para s a -> TM ps s a Source #

Add a new paragraph to the text

endPara :: Style s => Para s () Source #

startPara :: Style s => Para s () Source #

Functions useful to change the paragraph style

getParaStyle :: TM ps s ps Source #

Get the current paragraph style

setParaStyle :: ParagraphStyle ps s => ps -> TM ps s () Source #

Change the current paragraph style

getWritingSystem :: TM ps s WritingSystem Source #

Get the current writing system for the paragraph

Container

mkContainer Source #

Arguments

:: PDFFloat

x

-> PDFFloat

y

-> PDFFloat

width

-> PDFFloat

height

-> PDFFloat

Pargraph tolerance

-> Container ps s

New container

Create a empty container to constraint the amount of line that can be displayed

fillContainer Source #

Arguments

:: (ParagraphStyle ps s, ComparableStyle ps) 
=> VerState ps

Vertical style for interline glues

-> Container ps s

Container

-> [VBox ps s]

VBox to add

-> (Draw (), Container ps s, [VBox ps s])

Component to draw, new container and remaining VBoxes due to overfull container

Fill a container with lines

defaultVerState :: s -> VerState s Source #

Default vertical state

Default values
baselineskip = (12,0.17,0.0)
lineskip = (3.0,0.33,0.0)
lineskiplimit = 2

getBoxes Source #

Arguments

:: ParagraphStyle ps s 
=> ps

default vertical style

-> s

Default horizontal style

-> TM ps s a

Typesetting monad

-> [VBox ps s]

List of boxes

Return the list of Vboxes for a text

containerX :: Container ps s -> PDFFloat Source #

Container horizontal position

containerY :: Container ps s -> PDFFloat Source #

Container vertical position

containerWidth :: Container ps s -> PDFFloat Source #

Get the width of the container

containerHeight :: Container ps s -> PDFFloat Source #

Get the height of the container

containerContentHeight :: Container ps s -> PDFFloat Source #

Get the content height of the container with glue dilatation

containerContentRightBorder :: Container ps s -> PDFFloat Source #

Get the maximum right border of the container content (maybe bigger than container width due to overfull lines)

containerContentLeftBorder :: Container ps s -> PDFFloat Source #

Get the minimum left border of the container content

containerCurrentHeight :: Container ps s -> PDFFloat Source #

Get the current height of the container without glue dilatation

containerContentRectangle :: Container ps s -> Rectangle Source #

Return the rectangle containing the text after formatting and glue dilatation

drawTextBox Source #

Arguments

:: (ParagraphStyle ps s, Style s) 
=> PDFFloat

x

-> PDFFloat

y

-> PDFFloat

width limit

-> PDFFloat

height limit

-> Orientation 
-> ps

default vertical style

-> s

Default horizontal style

-> TM ps s a

Typesetting monad

-> (Rectangle, Draw ()) 

Draw a text box with relative position. Useful for labels

Settings (similar to TeX ones)

Line breaking settings

setJustification Source #

Arguments

:: Justification

Centered, left or fully justified

-> TM ps s () 

Vertical mode settings

Styles