| Copyright | (c) 2006-2016 alpheccar.org |
|---|---|
| License | BSD-style |
| Maintainer | misc@NOSPAMalpheccar.org |
| Stability | experimental |
| Portability | portable |
| Safe Haskell | Safe-Inferred |
| Language | Haskell2010 |
Graphics.PDF.Typesetting
Description
Experimental typesetting. It is a work in progress
Synopsis
- class Box a where
- class DisplayableBox a where
- data Letter s
- type BoxDimension = (PDFFloat, PDFFloat, PDFFloat)
- class ComparableStyle a => Style a where
- sentenceStyle :: a -> Maybe (Rectangle -> Draw b -> Draw ())
- wordStyle :: a -> Maybe (Rectangle -> StyleFunction -> Draw b -> Draw ())
- textStyle :: a -> TextStyle
- 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
- class (ComparableStyle a, Style s) => ParagraphStyle a s | a -> s where
- class (Style s, Monad m) => MonadStyle s m | m -> s where
- class ComparableStyle a where
- isSameStyleAs :: a -> a -> Bool
- data Para s a
- data TM ps s a
- data VBox ps s
- data VerState s = VerState {
- baselineskip :: !(PDFFloat, PDFFloat, PDFFloat)
- lineskip :: !(PDFFloat, PDFFloat, PDFFloat)
- lineskiplimit :: !PDFFloat
- currentParagraphStyle :: !s
- data Container ps s
- data Justification
- data Orientation
- displayFormattedText :: ParagraphStyle ps s => Rectangle -> ps -> s -> TM ps s a -> Draw a
- styleFont :: Style s => s -> AnyFont
- txt :: Style s => Text -> Para s ()
- kern :: Style s => PDFFloat -> Para s ()
- addPenalty :: Int -> Para s ()
- mkLetter :: (Show a, Box a, DisplayableBox a) => BoxDimension -> Maybe s -> a -> Letter s
- mkDrawBox :: Draw () -> DrawBox
- forceNewLine :: Style s => Para s ()
- paragraph :: Style s => Para s a -> TM ps s a
- endPara :: Style s => Para s ()
- startPara :: Style s => Para s ()
- getParaStyle :: TM ps s ps
- setParaStyle :: ParagraphStyle ps s => ps -> TM ps s ()
- getWritingSystem :: TM ps s WritingSystem
- setWritingSystem :: WritingSystem -> TM ps s ()
- mkContainer :: PDFFloat -> PDFFloat -> PDFFloat -> PDFFloat -> PDFFloat -> Container ps s
- fillContainer :: (ParagraphStyle ps s, ComparableStyle ps) => VerState ps -> Container ps s -> [VBox ps s] -> (Draw (), Container ps s, [VBox ps s])
- defaultVerState :: s -> VerState s
- getBoxes :: ParagraphStyle ps s => ps -> s -> TM ps s a -> [VBox ps s]
- containerX :: Container ps s -> PDFFloat
- containerY :: Container ps s -> PDFFloat
- containerWidth :: Container ps s -> PDFFloat
- containerHeight :: Container ps s -> PDFFloat
- containerContentHeight :: Container ps s -> PDFFloat
- containerContentRightBorder :: Container ps s -> PDFFloat
- containerContentLeftBorder :: Container ps s -> PDFFloat
- containerCurrentHeight :: Container ps s -> PDFFloat
- containerContentRectangle :: Container ps s -> Rectangle
- drawTextBox :: (ParagraphStyle ps s, Style s) => PDFFloat -> PDFFloat -> PDFFloat -> PDFFloat -> Orientation -> ps -> s -> TM ps s a -> (Rectangle, Draw ())
- setFirstPassTolerance :: PDFFloat -> TM ps s ()
- setSecondPassTolerance :: PDFFloat -> TM ps s ()
- setHyphenPenaltyValue :: Int -> TM ps s ()
- setFitnessDemerit :: PDFFloat -> TM ps s ()
- setHyphenDemerit :: PDFFloat -> TM ps s ()
- setLinePenalty :: PDFFloat -> TM ps s ()
- getFirstPassTolerance :: TM ps s PDFFloat
- getSecondPassTolerance :: TM ps s PDFFloat
- getHyphenPenaltyValue :: TM ps s Int
- getFitnessDemerit :: TM ps s PDFFloat
- getHyphenDemerit :: TM ps s PDFFloat
- getLinePenalty :: TM ps s PDFFloat
- setJustification :: Justification -> TM ps s ()
- setBaseLineSkip :: PDFFloat -> PDFFloat -> PDFFloat -> TM ps s ()
- setLineSkipLimit :: PDFFloat -> TM ps s ()
- setLineSkip :: PDFFloat -> PDFFloat -> PDFFloat -> TM ps s ()
- getBaseLineSkip :: TM ps s (PDFFloat, PDFFloat, PDFFloat)
- getLineSkipLimit :: TM ps s PDFFloat
- getLineSkip :: TM ps s (PDFFloat, PDFFloat, PDFFloat)
- data StandardStyle = Font PDFFont Color Color
- data StandardParagraphStyle = NormalParagraph
Types
Boxes
A box is an object with dimensions and used in the typesetting process
Minimal complete definition
Methods
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
Instances
| Box BoxDimension Source # | |
Defined in Graphics.PDF.Typesetting.Box Methods boxWidth :: BoxDimension -> PDFFloat Source # boxHeight :: BoxDimension -> PDFFloat Source # boxDescent :: BoxDimension -> PDFFloat Source # boxAscent :: BoxDimension -> PDFFloat Source # | |
| Box (VBox ps s) Source # | |
class DisplayableBox a where Source #
A box that can be displayed
Methods
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 # | |
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 |
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
Methods
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)
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
Instances
| Style StandardStyle Source # | |
Defined in Graphics.PDF.Typesetting.StandardStyle Methods sentenceStyle :: StandardStyle -> Maybe (Rectangle -> Draw b -> Draw ()) Source # wordStyle :: StandardStyle -> Maybe (Rectangle -> StyleFunction -> Draw b -> Draw ()) Source # textStyle :: StandardStyle -> TextStyle Source # updateStyle :: StandardStyle -> StandardStyle Source # styleHeight :: StandardStyle -> PDFFloat Source # styleDescent :: StandardStyle -> PDFFloat Source # | |
Text style used by PDF operators
Constructors
| TextStyle | |
Fields
| |
data StyleFunction Source #
What kind of style drawing function is required for a word when word styling is enabled
Instances
| Eq StyleFunction Source # | |
Defined in Graphics.PDF.Typesetting.Box Methods (==) :: StyleFunction -> StyleFunction -> Bool # (/=) :: StyleFunction -> StyleFunction -> Bool # | |
class (ComparableStyle a, Style s) => ParagraphStyle a s | a -> s where Source #
Paragraph style
Minimal complete definition
Nothing
Methods
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
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
How to style the interline glues added in a paragraph by the line breaking algorithm
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
Get the paragraph bounding box and the paragraph draw command to apply additional effects
Instances
| ParagraphStyle StandardParagraphStyle StandardStyle Source # | |
Defined in Graphics.PDF.Typesetting.StandardStyle Methods lineWidth :: StandardParagraphStyle -> PDFFloat -> Int -> PDFFloat Source # linePosition :: StandardParagraphStyle -> PDFFloat -> Int -> PDFFloat Source # interline :: StandardParagraphStyle -> Maybe (Rectangle -> Draw ()) Source # paragraphChange :: StandardParagraphStyle -> Int -> [Letter StandardStyle] -> (StandardParagraphStyle, [Letter StandardStyle]) Source # paragraphStyle :: StandardParagraphStyle -> Maybe (Rectangle -> Draw b -> Draw ()) Source # | |
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
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)
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
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 # | |
Defined in Graphics.PDF.Typesetting Methods setStyle :: s -> Para s () Source # currentStyle :: Para s s Source # addBox :: (Show a, DisplayableBox a, Box a) => a -> PDFFloat -> PDFFloat -> PDFFloat -> Para s () Source # glue :: PDFFloat -> PDFFloat -> PDFFloat -> Para s () Source # unstyledGlue :: PDFFloat -> PDFFloat -> PDFFloat -> Para s () Source # | |
| Style s => MonadStyle s (TM ps s) Source # | |
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 #
Instances
| ComparableStyle StandardParagraphStyle Source # | |
Defined in Graphics.PDF.Typesetting.StandardStyle Methods isSameStyleAs :: StandardParagraphStyle -> StandardParagraphStyle -> Bool Source # | |
| ComparableStyle StandardStyle Source # | |
Defined in Graphics.PDF.Typesetting.StandardStyle Methods isSameStyleAs :: StandardStyle -> StandardStyle -> Bool Source # | |
Typesetting monads
Instances
| Style s => MonadStyle s (Para s) Source # | |
Defined in Graphics.PDF.Typesetting Methods setStyle :: s -> Para s () Source # currentStyle :: Para s s Source # addBox :: (Show a, DisplayableBox a, Box a) => a -> PDFFloat -> PDFFloat -> PDFFloat -> Para s () Source # glue :: PDFFloat -> PDFFloat -> PDFFloat -> Para s () Source # unstyledGlue :: PDFFloat -> PDFFloat -> PDFFloat -> Para s () Source # | |
| MonadState s (Para s) Source # | |
| Applicative (Para s) Source # | |
| Functor (Para s) Source # | |
| Monad (Para s) Source # | |
| MonadWriter [Letter s] (Para s) Source # | |
Instances
| Style s => MonadStyle s (TM ps s) Source # | |
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 # | |
| Applicative (TM ps s) Source # | |
| Functor (TM ps s) Source # | |
| Monad (TM ps s) Source # | |
Containers
Constructors
| VerState | |
Fields
| |
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 Justification Source #
Constructors
| FullJustification | |
| Centered | |
| LeftJustification | |
| RightJustification |
Instances
| Eq Justification Source # | |
Defined in Graphics.PDF.Typesetting.Breaking Methods (==) :: Justification -> Justification -> Bool # (/=) :: Justification -> Justification -> Bool # | |
data Orientation Source #
Instances
| Show Orientation Source # | |
Defined in Graphics.PDF.Typesetting Methods showsPrec :: Int -> Orientation -> ShowS # show :: Orientation -> String # showList :: [Orientation] -> ShowS # | |
| Eq Orientation Source # | |
Defined in Graphics.PDF.Typesetting | |
Functions
Text display
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
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
Paragraph construction operators
forceNewLine :: Style s => Para s () Source #
For a newline and end the current paragraph
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
setWritingSystem :: WritingSystem -> TM ps s () Source #
Container
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
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
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
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
setFirstPassTolerance :: PDFFloat -> TM ps s () Source #
setSecondPassTolerance :: PDFFloat -> TM ps s () Source #
setHyphenPenaltyValue :: Int -> TM ps s () Source #
setFitnessDemerit :: PDFFloat -> TM ps s () Source #
setHyphenDemerit :: PDFFloat -> TM ps s () Source #
setLinePenalty :: PDFFloat -> TM ps s () Source #
getFirstPassTolerance :: TM ps s PDFFloat Source #
getSecondPassTolerance :: TM ps s PDFFloat Source #
getHyphenPenaltyValue :: TM ps s Int Source #
getFitnessDemerit :: TM ps s PDFFloat Source #
getHyphenDemerit :: TM ps s PDFFloat Source #
getLinePenalty :: TM ps s PDFFloat Source #
Arguments
| :: Justification | Centered, left or fully justified |
| -> TM ps s () |
Vertical mode settings
setLineSkipLimit :: PDFFloat -> TM ps s () Source #
getLineSkipLimit :: TM ps s PDFFloat Source #
Styles
data StandardStyle Source #
Standard styles for sentences
Instances
data StandardParagraphStyle Source #
Standard styles for paragraphs
Constructors
| NormalParagraph |
Instances
| ComparableStyle StandardParagraphStyle Source # | |
Defined in Graphics.PDF.Typesetting.StandardStyle Methods isSameStyleAs :: StandardParagraphStyle -> StandardParagraphStyle -> Bool Source # | |
| ParagraphStyle StandardParagraphStyle StandardStyle Source # | |
Defined in Graphics.PDF.Typesetting.StandardStyle Methods lineWidth :: StandardParagraphStyle -> PDFFloat -> Int -> PDFFloat Source # linePosition :: StandardParagraphStyle -> PDFFloat -> Int -> PDFFloat Source # interline :: StandardParagraphStyle -> Maybe (Rectangle -> Draw ()) Source # paragraphChange :: StandardParagraphStyle -> Int -> [Letter StandardStyle] -> (StandardParagraphStyle, [Letter StandardStyle]) Source # paragraphStyle :: StandardParagraphStyle -> Maybe (Rectangle -> Draw b -> Draw ()) Source # | |