HPDF-1.1: Generation of PDF documentsContentsIndex
Graphics.PDF.Typesetting
Portabilityportable
Stabilityexperimental
Maintainermisc@NOSPAMalpheccar.org
Contents
Typesetting
Types
Functions
Text display
Text construction operators
Paragraph construction operators
Misc
Settings (similar to TeX ones)
Line breaking settings
Vertical mode settings
Styles
Functions useful to change the paragraph style
Description
Experimental typesetting. It is a work in progress
Synopsis
class Box a where
boxWidth :: a -> PDFFloat
boxHeight :: a -> PDFFloat
boxDescent :: a -> PDFFloat
boxAscent :: a -> PDFFloat
class DisplayableBox a where
strokeBox :: a -> PDFFloat -> PDFFloat -> Draw ()
class Style a where
sentenceStyle :: a -> Maybe (Rectangle -> Draw b -> Draw ())
wordStyle :: a -> Maybe (Rectangle -> StyleFunction -> Draw b -> Draw ())
textStyle :: a -> TextStyle
styleCode :: a -> Int
updateStyle :: a -> a
styleHeight :: a -> PDFFloat
styleDescent :: a -> PDFFloat
data TextStyle = TextStyle {
textFont :: !PDFFont
textStrokeColor :: !Color
textFillColor :: !Color
textMode :: !TextMode
penWidth :: !PDFFloat
scaleSpace :: !PDFFloat
scaleDilatation :: !PDFFloat
scaleCompression :: !PDFFloat
}
data StyleFunction
= DrawWord
| DrawGlue
data AnyStyle
class ParagraphStyle a where
lineWidth :: a -> PDFFloat -> Int -> PDFFloat
linePosition :: a -> PDFFloat -> Int -> PDFFloat
paraStyleCode :: a -> Int
interline :: a -> Maybe (Rectangle -> Draw ())
paraChange :: a -> [Letter] -> (a, [Letter])
paragraphStyle :: a -> Maybe (Rectangle -> Draw b -> Draw ())
data AnyParagraphStyle
class Monad m => MonadStyle m where
setStyle :: Style a => a -> m ()
currentStyle :: m AnyStyle
addBox :: (Show a, DisplayableBox a, Box a) => a -> PDFFloat -> PDFFloat -> PDFFloat -> m ()
glue :: PDFFloat -> PDFFloat -> PDFFloat -> m ()
unstyledGlue :: PDFFloat -> PDFFloat -> PDFFloat -> m ()
data Letter
= Letter BoxDimension !AnyBox !(Maybe AnyStyle)
| Glue !PDFFloat !PDFFloat !PDFFloat !(Maybe AnyStyle)
| FlaggedPenalty !PDFFloat !Int !AnyStyle
| Penalty !Int
| AChar !AnyStyle !Char !PDFFloat
| Kern !PDFFloat !(Maybe AnyStyle)
type BoxDimension = (PDFFloat, PDFFloat, PDFFloat)
displayFormattedText :: (Style s, ParagraphStyle s') => Rectangle -> s' -> s -> TM a -> Draw a
endParagraph :: Bool -> Para ()
txt :: String -> Para ()
paragraph :: Para a -> TM a
kern :: PDFFloat -> Para ()
addPenalty :: Int -> Para ()
mkLetter :: (Show a, Box a, DisplayableBox a) => BoxDimension -> Maybe AnyStyle -> a -> Letter
mkDrawBox :: Draw () -> DrawBox
setFirstPassTolerance :: PDFFloat -> TM ()
setSecondPassTolerance :: PDFFloat -> TM ()
setHyphenPenaltyValue :: Int -> TM ()
setFitnessDemerit :: PDFFloat -> TM ()
setHyphenDemerit :: PDFFloat -> TM ()
setLinePenalty :: PDFFloat -> TM ()
getFirstPassTolerance :: TM PDFFloat
getSecondPassTolerance :: TM PDFFloat
getHyphenPenaltyValue :: TM Int
getFitnessDemerit :: TM PDFFloat
getHyphenDemerit :: TM PDFFloat
getLinePenalty :: TM PDFFloat
setBaseLineSkip :: PDFFloat -> PDFFloat -> PDFFloat -> TM ()
setLineSkipLimit :: PDFFloat -> TM ()
setLineSkip :: PDFFloat -> PDFFloat -> PDFFloat -> TM ()
getBaseLineSkip :: TM (PDFFloat, PDFFloat, PDFFloat)
getLineSkipLimit :: TM PDFFloat
getLineSkip :: TM (PDFFloat, PDFFloat, PDFFloat)
getParaStyle :: TM AnyParagraphStyle
setParaStyle :: ParagraphStyle s => s -> TM ()
getTextArea :: TM Rectangle
Typesetting
Types
class Box a where
A box is an object with dimensions and used in the typesetting process
Methods
boxWidth
:: aBox
-> PDFFloatWidth of the box
Box width
boxHeight :: a -> PDFFloat
Box height
boxDescent :: a -> PDFFloat
Distance between box bottom and box baseline
boxAscent :: a -> PDFFloat
Distance between box top and box baseline
show/hide Instances
Box AnyBox
Box BoxDimension
Box DrawBox
Box HBox
Box NullChar
Box Overfull
Box VBox
class DisplayableBox a where
A box that can be displayed
Methods
strokeBox
:: aThe box
-> PDFFloatHorizontal position
-> PDFFloatVertical position (top of the box and NOT baseline)
-> Draw ()
Draw a box
show/hide Instances
class Style a where
Style of text (sentences and words)
Methods
sentenceStyle
:: aThe 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
:: aThe style
-> Maybe (Rectangle -> StyleFunction -> Draw b -> Draw ())Word styling function
textStyle :: a -> TextStyle
styleCode :: a -> Int
All styles used in a document must have different style codes
updateStyle :: a -> a
A style may contain data changed from word to word
styleHeight :: a -> PDFFloat
A style may change the height of words
styleDescent :: a -> PDFFloat
A style may change the descent of lines
show/hide Instances
data TextStyle
Text style used by PDF operators
Constructors
TextStyle
textFont :: !PDFFont
textStrokeColor :: !Color
textFillColor :: !Color
textMode :: !TextMode
penWidth :: !PDFFloat
scaleSpace :: !PDFFloatScaling factor for normal space size (scale also the dilation and compression factors)
scaleDilatation :: !PDFFloatScale the dilation factor of glues
scaleCompression :: !PDFFloatScale the compression factor of glues
show/hide Instances
data StyleFunction
What kind of style drawing function is required for a word when word styling is enabled
Constructors
DrawWordMust style a word
DrawGlueMust style a glue
show/hide Instances
data AnyStyle
Any sentence style
show/hide Instances
class ParagraphStyle a where
Paragraph style
Methods
lineWidth
:: aThe style
-> PDFFloatWidth of the text area used by the typesetting algorithm
-> IntLine number
-> PDFFloatLine width
Width of the line of the paragraph
linePosition
:: aThe style
-> PDFFloatWidth of the text area used by the typesetting algorithm
-> IntLine number
-> PDFFloatHorizontal 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
paraStyleCode
:: aThe style
-> IntCode identifying the style
All paragraph styles used in a document must have different codes
interline
:: aThe 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
paraChange
:: aThe style
-> [Letter]List of letters in the paragraph
-> (a, [Letter])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
:: aThe 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
show/hide Instances
data AnyParagraphStyle
Any paragraph style
show/hide Instances
class Monad m => MonadStyle m where
A MonadStyle where some typesetting operators can be used
Methods
setStyle :: Style a => a -> m ()
Set the current text style
currentStyle :: m AnyStyle
Get the current text style
addBox
:: (Show a, DisplayableBox a, Box a)
=> a
-> PDFFloatWidth
-> PDFFloatHeight
-> PDFFloatDescent
-> m ()
Add a box using the current mode (horizontal or vertical. The current style is always applied to the added box)
glue
:: PDFFloatSize of glue (width or height depending on the mode)
-> PDFFloatDilatation factor
-> PDFFloatCompression factor
-> m ()
Add a glue using the current style
unstyledGlue
:: PDFFloatSize of glue (width or height depending on the mode)
-> PDFFloatDilatation factor
-> PDFFloatCompression factor
-> m ()
Add a glue with no style (it is just a translation)
show/hide Instances
data Letter
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 AnyStyle)Any box as a letter
Glue !PDFFloat !PDFFloat !PDFFloat !(Maybe AnyStyle)A glue with style to know if it is part of the same sentence
FlaggedPenalty !PDFFloat !Int !AnyStyleHyphen point
Penalty !IntPenalty
AChar !AnyStyle !Char !PDFFloatA char
Kern !PDFFloat !(Maybe AnyStyle)A kern : non dilatable and non breakable glue
show/hide Instances
type BoxDimension = (PDFFloat, PDFFloat, PDFFloat)
Dimension of a box : width, height and descent
Functions
Text display
displayFormattedText
:: (Style s, ParagraphStyle s')
=> RectangleText area
-> s'default vertical style
-> sDefault horizontal style
-> TM aTypesetting monad
-> Draw aDraw 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
endParagraph
:: BoolTrue if we use the same style to end a paragraph. false for an invisible style
-> Para ()
End the current paragraph with or without using the same style
txt :: String -> Para ()

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

Add a text line

paragraph :: Para a -> TM a
Add a new paragraph to the text
Paragraph construction operators
kern :: PDFFloat -> Para ()
add a kern (space that can be dilated or compressed and on which no line breaking can occur)
addPenalty :: Int -> Para ()
Add a penalty
mkLetter
:: (Show a, Box a, DisplayableBox a)
=> BoxDimensionDimension of the box
-> Maybe AnyStyleText style of the box (can use t)
-> aBox
-> Letter
Make a letter from any box
Misc
mkDrawBox :: Draw () -> DrawBox
Make a drawing box. A box object containing a Draw value
Settings (similar to TeX ones)
Line breaking settings
setFirstPassTolerance :: PDFFloat -> TM ()
setSecondPassTolerance :: PDFFloat -> TM ()
setHyphenPenaltyValue :: Int -> TM ()
setFitnessDemerit :: PDFFloat -> TM ()
setHyphenDemerit :: PDFFloat -> TM ()
setLinePenalty :: PDFFloat -> TM ()
getFirstPassTolerance :: TM PDFFloat
getSecondPassTolerance :: TM PDFFloat
getHyphenPenaltyValue :: TM Int
getFitnessDemerit :: TM PDFFloat
getHyphenDemerit :: TM PDFFloat
getLinePenalty :: TM PDFFloat
Vertical mode settings
setBaseLineSkip :: PDFFloat -> PDFFloat -> PDFFloat -> TM ()
setLineSkipLimit :: PDFFloat -> TM ()
setLineSkip :: PDFFloat -> PDFFloat -> PDFFloat -> TM ()
getBaseLineSkip :: TM (PDFFloat, PDFFloat, PDFFloat)
getLineSkipLimit :: TM PDFFloat
getLineSkip :: TM (PDFFloat, PDFFloat, PDFFloat)
Styles
Functions useful to change the paragraph style
getParaStyle :: TM AnyParagraphStyle
Get the current paragraph style
setParaStyle :: ParagraphStyle s => s -> TM ()
Change the current paragraph style
getTextArea :: TM Rectangle
Get the bounding rectangle containing the text
Produced by Haddock version 0.8