Copyright | (c) 2006-2016 alpheccar.org |
---|---|
License | BSD-style |
Maintainer | misc@NOSPAMalpheccar.org |
Stability | experimental |
Portability | portable |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Generation of PDF documents A PDF library with support for several pages, page transitions, outlines, annotations, compression, colors, shapes, patterns, jpegs, fonts, typesetting ... Have a look at the Graphics.PDF.Documentation module to see how to use it. Or, download the package and look at the test.hs file in the Test folder. That file is giving an example of each feature.
Synopsis
- data PDF a
- runPdf :: String -> PDFDocumentInfo -> PDFRect -> PDF a -> IO ()
- pdfByteString :: PDFDocumentInfo -> PDFRect -> PDF a -> ByteString
- data PDFRect = PDFRect !Double !Double !Double !Double
- type PDFFloat = Double
- data PDFReference s
- data PDFString
- data PDFPage
- data Pages
- data Draw a
- data PDFXForm
- data PDFTransition = PDFTransition !PDFFloat !PDFTransStyle
- data PDFTransStyle
- data PDFTransDirection
- data PDFTransDimension
- data PDFTransDirection2
- data PDFDocumentInfo = PDFDocumentInfo {}
- data PDFDocumentPageMode
- data PDFDocumentPageLayout
- data PDFViewerPreferences = PDFViewerPreferences {}
- class PDFXObject a where
- drawXObject :: PDFReference a -> Draw ()
- class PDFGlobals m where
- bounds :: PDFXObject a => PDFReference a -> m (PDFFloat, PDFFloat)
- addPage :: Maybe PDFRect -> PDF (PDFReference PDFPage)
- addPageWithTransition :: Maybe PDFRect -> Maybe PDFFloat -> Maybe PDFTransition -> PDF (PDFReference PDFPage)
- drawWithPage :: PDFReference PDFPage -> Draw a -> PDF a
- createPDFXForm :: PDFFloat -> PDFFloat -> PDFFloat -> PDFFloat -> Draw a -> PDF (PDFReference PDFXForm)
- standardDocInfo :: PDFDocumentInfo
- standardViewerPrefs :: PDFViewerPreferences
- withNewContext :: Draw a -> Draw a
- emptyDrawing :: Draw ()
- module Graphics.PDF.Shapes
- module Graphics.PDF.Colors
- module Graphics.PDF.Coordinates
- applyMatrix :: Matrix -> Draw ()
- module Graphics.PDF.Text
- module Graphics.PDF.Navigation
- module Graphics.PDF.Annotation
- module Graphics.PDF.Action
- module Graphics.PDF.Image
- module Graphics.PDF.Pattern
- module Graphics.PDF.Shading
- module Graphics.PDF.Transparency
- data ColorSpace a e where
- GraySpace :: ColorSpace PDFFloat ExprFloat
- RGBSpace :: ColorSpace FloatRGB ExprRGB
- CMYKSpace :: ColorSpace FloatCMYK ExprCMYK
- calculator1 :: (ExprFloat -> e) -> Function1 Global a e
- calculator2 :: (ExprFloat -> ExprFloat -> e) -> Function2 Global a e
- data ColorFunction1 = forall a e.(ColorTuple a, Result e) => ColorFunction1 (ColorSpace a e) (Function1 Local a e)
- data ColorFunction2 = forall a e.(ColorTuple a, Result e) => ColorFunction2 (ColorSpace a e) (Function2 Local a e)
- data Function1 scope a e where
- GlobalFunction1 :: FunctionObject (PDFFloat -> a) (ExprFloat -> e) -> Function1 Local a e
- Sampled1 :: Array Int a -> Function1 Global a e
- Interpolated1 :: PDFFloat -> a -> a -> Function1 scope a e
- Stitched1 :: Function1 Local a e -> [(PDFFloat, Function1 Local a e)] -> Function1 scope a e
- Calculator1 :: (ExprFloat -> e) -> Function1 Global a e
- data Function2 scope a e where
- GlobalFunction2 :: FunctionObject (PDFFloat -> PDFFloat -> a) (ExprFloat -> ExprFloat -> e) -> Function2 Local a e
- Sampled2 :: Array (Int, Int) a -> Function2 Global a e
- Calculator2 :: (ExprFloat -> ExprFloat -> e) -> Function2 Global a e
- data Global
- data Local
- linearStitched :: ColorTuple a => a -> [(PDFFloat, a)] -> a -> Function1 Local a e
- data FunctionObject a e
- module Graphics.PDF.Fonts.Font
- module Graphics.PDF.Fonts.StandardFont
- module Graphics.PDF.Fonts.Type1
- readType1Font :: FilePath -> FilePath -> IO (Either ParseError Type1FontStructure)
- mkType1Font :: Type1FontStructure -> PDF AnyFont
- module Graphics.PDF.Typesetting
HPDF
PDF Monad
The PDF Monad
Instances
PDFGlobals PDF Source # | |
Defined in Graphics.PDF.Draw bounds :: PDFXObject a => PDFReference a -> PDF (PDFFloat, PDFFloat) Source # | |
Applicative PDF Source # | |
Functor PDF Source # | |
Monad PDF Source # | |
:: String | Name of the PDF document |
-> PDFDocumentInfo | |
-> PDFRect | Default size for a page |
-> PDF a | PDF action |
-> IO () |
Generates a PDF document
:: PDFDocumentInfo | |
-> PDFRect | Default size for a page |
-> PDF a | PDF action |
-> ByteString |
Generate a lazy bytestring for the PDF
PDF Common Types
data PDFReference s Source #
A reference to a PDF object
Instances
A PDFString containing a strict bytestring (serialied as UTF16BE)
A PDF Page object
Document management
The drawing monad
Instances
PDFGlobals Draw Source # | |
Defined in Graphics.PDF.Draw bounds :: PDFXObject a => PDFReference a -> Draw (PDFFloat, PDFFloat) Source # | |
Applicative Draw Source # | |
Functor Draw Source # | |
Monad Draw Source # | |
MonadWriter Builder Draw Source # | |
Instances
PDFXObject PDFXForm Source # | |
Defined in Graphics.PDF.Draw drawXObject :: PDFReference PDFXForm -> Draw () Source # privateDrawXObject :: PDFReference PDFXForm -> Draw () |
data PDFTransition Source #
A PDF Transition
Instances
Eq PDFTransition Source # | |
Defined in Graphics.PDF.Draw (==) :: PDFTransition -> PDFTransition -> Bool # (/=) :: PDFTransition -> PDFTransition -> Bool # |
data PDFTransStyle Source #
Transition style
Split PDFTransDimension PDFTransDirection | |
Blinds PDFTransDimension | |
Box PDFTransDirection | |
Wipe PDFTransDirection2 | |
Dissolve | |
Glitter PDFTransDirection2 |
Instances
Show PDFTransStyle Source # | |
Defined in Graphics.PDF.Draw showsPrec :: Int -> PDFTransStyle -> ShowS # show :: PDFTransStyle -> String # showList :: [PDFTransStyle] -> ShowS # | |
Eq PDFTransStyle Source # | |
Defined in Graphics.PDF.Draw (==) :: PDFTransStyle -> PDFTransStyle -> Bool # (/=) :: PDFTransStyle -> PDFTransStyle -> Bool # |
data PDFTransDirection Source #
Direction of a transition
Instances
Show PDFTransDirection Source # | |
Defined in Graphics.PDF.Draw showsPrec :: Int -> PDFTransDirection -> ShowS # show :: PDFTransDirection -> String # showList :: [PDFTransDirection] -> ShowS # | |
Eq PDFTransDirection Source # | |
Defined in Graphics.PDF.Draw (==) :: PDFTransDirection -> PDFTransDirection -> Bool # (/=) :: PDFTransDirection -> PDFTransDirection -> Bool # |
data PDFTransDimension Source #
Dimension of a transition
Instances
Show PDFTransDimension Source # | |
Defined in Graphics.PDF.Draw showsPrec :: Int -> PDFTransDimension -> ShowS # show :: PDFTransDimension -> String # showList :: [PDFTransDimension] -> ShowS # | |
Eq PDFTransDimension Source # | |
Defined in Graphics.PDF.Draw (==) :: PDFTransDimension -> PDFTransDimension -> Bool # (/=) :: PDFTransDimension -> PDFTransDimension -> Bool # |
data PDFTransDirection2 Source #
Direction of a transition
LeftToRight | |
BottomToTop | Wipe only |
RightToLeft | Wipe only |
TopToBottom | |
TopLeftToBottomRight | Glitter only |
Instances
Eq PDFTransDirection2 Source # | |
Defined in Graphics.PDF.Draw (==) :: PDFTransDirection2 -> PDFTransDirection2 -> Bool # (/=) :: PDFTransDirection2 -> PDFTransDirection2 -> Bool # |
data PDFDocumentInfo Source #
Document metadata
data PDFDocumentPageMode Source #
Document page mode
Instances
Show PDFDocumentPageMode Source # | |
Defined in Graphics.PDF.Draw showsPrec :: Int -> PDFDocumentPageMode -> ShowS # show :: PDFDocumentPageMode -> String # showList :: [PDFDocumentPageMode] -> ShowS # | |
Eq PDFDocumentPageMode Source # | |
Defined in Graphics.PDF.Draw (==) :: PDFDocumentPageMode -> PDFDocumentPageMode -> Bool # (/=) :: PDFDocumentPageMode -> PDFDocumentPageMode -> Bool # |
data PDFDocumentPageLayout Source #
Document page layout
Instances
Show PDFDocumentPageLayout Source # | |
Defined in Graphics.PDF.Draw showsPrec :: Int -> PDFDocumentPageLayout -> ShowS # show :: PDFDocumentPageLayout -> String # showList :: [PDFDocumentPageLayout] -> ShowS # | |
Eq PDFDocumentPageLayout Source # | |
Defined in Graphics.PDF.Draw (==) :: PDFDocumentPageLayout -> PDFDocumentPageLayout -> Bool # (/=) :: PDFDocumentPageLayout -> PDFDocumentPageLayout -> Bool # |
data PDFViewerPreferences Source #
Viewer preferences
PDFViewerPreferences | |
|
class PDFXObject a where Source #
A PDF Xobject which can be drawn
Nothing
drawXObject :: PDFReference a -> Draw () Source #
Instances
PDFXObject PDFXForm Source # | |
Defined in Graphics.PDF.Draw drawXObject :: PDFReference PDFXForm -> Draw () Source # privateDrawXObject :: PDFReference PDFXForm -> Draw () | |
PDFXObject PDFJpeg Source # | |
Defined in Graphics.PDF.Image drawXObject :: PDFReference PDFJpeg -> Draw () Source # privateDrawXObject :: PDFReference PDFJpeg -> Draw () | |
PDFXObject RawImage Source # | |
Defined in Graphics.PDF.Image drawXObject :: PDFReference RawImage -> Draw () Source # privateDrawXObject :: PDFReference RawImage -> Draw () |
class PDFGlobals m where Source #
bounds :: PDFXObject a => PDFReference a -> m (PDFFloat, PDFFloat) Source #
Instances
PDFGlobals Draw Source # | |
Defined in Graphics.PDF.Draw bounds :: PDFXObject a => PDFReference a -> Draw (PDFFloat, PDFFloat) Source # | |
PDFGlobals PDF Source # | |
Defined in Graphics.PDF.Draw bounds :: PDFXObject a => PDFReference a -> PDF (PDFFloat, PDFFloat) Source # |
:: Maybe PDFRect | Page size or default document's one |
-> PDF (PDFReference PDFPage) | Reference to the new page |
Add a new page to a PDF document
addPageWithTransition Source #
:: Maybe PDFRect | Page size or default document's one |
-> Maybe PDFFloat | Optional duration |
-> Maybe PDFTransition | Optional transition |
-> PDF (PDFReference PDFPage) | Reference to the new page |
:: PDFReference PDFPage | Page |
-> Draw a | Drawing commands |
-> PDF a |
Draw on a given page
:: PDFFloat | Left |
-> PDFFloat | Bottom |
-> PDFFloat | Right |
-> PDFFloat | Top |
-> Draw a | Drawing commands |
-> PDF (PDFReference PDFXForm) |
Create a PDF XObject
standardDocInfo :: PDFDocumentInfo Source #
No information for the document
withNewContext :: Draw a -> Draw a Source #
Draw in a new drawing context without perturbing the previous context that is restored after the draw
emptyDrawing :: Draw () Source #
An empty drawing
Drawing
module Graphics.PDF.Shapes
Colors
module Graphics.PDF.Colors
Geometry
module Graphics.PDF.Coordinates
applyMatrix :: Matrix -> Draw () Source #
Apply a transformation matrix to the current coordinate frame
Text
module Graphics.PDF.Text
Navigation
module Graphics.PDF.Navigation
Annotations
module Graphics.PDF.Annotation
Actions
module Graphics.PDF.Action
Images
module Graphics.PDF.Image
Patterns
module Graphics.PDF.Pattern
Shading
module Graphics.PDF.Shading
Transparency
module Graphics.PDF.Transparency
data ColorSpace a e where Source #
GraySpace :: ColorSpace PDFFloat ExprFloat | |
RGBSpace :: ColorSpace FloatRGB ExprRGB | |
CMYKSpace :: ColorSpace FloatCMYK ExprCMYK |
Instances
Eq (ColorSpace a e) Source # | |
Defined in Graphics.PDF.Draw (==) :: ColorSpace a e -> ColorSpace a e -> Bool # (/=) :: ColorSpace a e -> ColorSpace a e -> Bool # | |
Ord (ColorSpace a e) Source # | |
Defined in Graphics.PDF.Draw compare :: ColorSpace a e -> ColorSpace a e -> Ordering # (<) :: ColorSpace a e -> ColorSpace a e -> Bool # (<=) :: ColorSpace a e -> ColorSpace a e -> Bool # (>) :: ColorSpace a e -> ColorSpace a e -> Bool # (>=) :: ColorSpace a e -> ColorSpace a e -> Bool # max :: ColorSpace a e -> ColorSpace a e -> ColorSpace a e # min :: ColorSpace a e -> ColorSpace a e -> ColorSpace a e # |
calculator1 :: (ExprFloat -> e) -> Function1 Global a e Source #
calculator2 :: (ExprFloat -> ExprFloat -> e) -> Function2 Global a e Source #
data ColorFunction1 Source #
forall a e.(ColorTuple a, Result e) => ColorFunction1 (ColorSpace a e) (Function1 Local a e) |
Instances
Eq ColorFunction1 Source # | |
Defined in Graphics.PDF.Draw (==) :: ColorFunction1 -> ColorFunction1 -> Bool # (/=) :: ColorFunction1 -> ColorFunction1 -> Bool # | |
Ord ColorFunction1 Source # | |
Defined in Graphics.PDF.Draw compare :: ColorFunction1 -> ColorFunction1 -> Ordering # (<) :: ColorFunction1 -> ColorFunction1 -> Bool # (<=) :: ColorFunction1 -> ColorFunction1 -> Bool # (>) :: ColorFunction1 -> ColorFunction1 -> Bool # (>=) :: ColorFunction1 -> ColorFunction1 -> Bool # max :: ColorFunction1 -> ColorFunction1 -> ColorFunction1 # min :: ColorFunction1 -> ColorFunction1 -> ColorFunction1 # |
data ColorFunction2 Source #
forall a e.(ColorTuple a, Result e) => ColorFunction2 (ColorSpace a e) (Function2 Local a e) |
Instances
Eq ColorFunction2 Source # | |
Defined in Graphics.PDF.Draw (==) :: ColorFunction2 -> ColorFunction2 -> Bool # (/=) :: ColorFunction2 -> ColorFunction2 -> Bool # | |
Ord ColorFunction2 Source # | |
Defined in Graphics.PDF.Draw compare :: ColorFunction2 -> ColorFunction2 -> Ordering # (<) :: ColorFunction2 -> ColorFunction2 -> Bool # (<=) :: ColorFunction2 -> ColorFunction2 -> Bool # (>) :: ColorFunction2 -> ColorFunction2 -> Bool # (>=) :: ColorFunction2 -> ColorFunction2 -> Bool # max :: ColorFunction2 -> ColorFunction2 -> ColorFunction2 # min :: ColorFunction2 -> ColorFunction2 -> ColorFunction2 # |
data Function1 scope a e where Source #
GlobalFunction1 :: FunctionObject (PDFFloat -> a) (ExprFloat -> e) -> Function1 Local a e | |
Sampled1 :: Array Int a -> Function1 Global a e | |
Interpolated1 :: PDFFloat -> a -> a -> Function1 scope a e | |
Stitched1 :: Function1 Local a e -> [(PDFFloat, Function1 Local a e)] -> Function1 scope a e | |
Calculator1 :: (ExprFloat -> e) -> Function1 Global a e |
Instances
(Local ~ scope, ColorTuple a, Eq a, Result e) => Eq (Function1 scope a e) Source # | |
(Local ~ scope, ColorTuple a, Ord a, Result e) => Ord (Function1 scope a e) Source # | |
Defined in Graphics.PDF.Draw compare :: Function1 scope a e -> Function1 scope a e -> Ordering # (<) :: Function1 scope a e -> Function1 scope a e -> Bool # (<=) :: Function1 scope a e -> Function1 scope a e -> Bool # (>) :: Function1 scope a e -> Function1 scope a e -> Bool # (>=) :: Function1 scope a e -> Function1 scope a e -> Bool # max :: Function1 scope a e -> Function1 scope a e -> Function1 scope a e # min :: Function1 scope a e -> Function1 scope a e -> Function1 scope a e # |
data Function2 scope a e where Source #
GlobalFunction2 :: FunctionObject (PDFFloat -> PDFFloat -> a) (ExprFloat -> ExprFloat -> e) -> Function2 Local a e | |
Sampled2 :: Array (Int, Int) a -> Function2 Global a e | |
Calculator2 :: (ExprFloat -> ExprFloat -> e) -> Function2 Global a e |
Instances
(Local ~ scope, ColorTuple a, Eq a, Result e) => Eq (Function2 scope a e) Source # | |
(Local ~ scope, ColorTuple a, Ord a, Result e) => Ord (Function2 scope a e) Source # | |
Defined in Graphics.PDF.Draw compare :: Function2 scope a e -> Function2 scope a e -> Ordering # (<) :: Function2 scope a e -> Function2 scope a e -> Bool # (<=) :: Function2 scope a e -> Function2 scope a e -> Bool # (>) :: Function2 scope a e -> Function2 scope a e -> Bool # (>=) :: Function2 scope a e -> Function2 scope a e -> Bool # max :: Function2 scope a e -> Function2 scope a e -> Function2 scope a e # min :: Function2 scope a e -> Function2 scope a e -> Function2 scope a e # |
data FunctionObject a e Source #
Instances
Eq (FunctionObject a e) Source # | |
Defined in Graphics.PDF.Draw (==) :: FunctionObject a e -> FunctionObject a e -> Bool # (/=) :: FunctionObject a e -> FunctionObject a e -> Bool # | |
Ord (FunctionObject a e) Source # | |
Defined in Graphics.PDF.Draw compare :: FunctionObject a e -> FunctionObject a e -> Ordering # (<) :: FunctionObject a e -> FunctionObject a e -> Bool # (<=) :: FunctionObject a e -> FunctionObject a e -> Bool # (>) :: FunctionObject a e -> FunctionObject a e -> Bool # (>=) :: FunctionObject a e -> FunctionObject a e -> Bool # max :: FunctionObject a e -> FunctionObject a e -> FunctionObject a e # min :: FunctionObject a e -> FunctionObject a e -> FunctionObject a e # |
Fonts
module Graphics.PDF.Fonts.Font
module Graphics.PDF.Fonts.Type1
readType1Font :: FilePath -> FilePath -> IO (Either ParseError Type1FontStructure) Source #
Create a type 1 font
Typesetting
module Graphics.PDF.Typesetting