{-# LANGUAGE CPP #-}
module Graphics.PDF.Document(
PDFXForm
, addPage
, addPageWithTransition
, drawWithPage
, createPDFXForm
, PDFTransition(..)
, PDFTransStyle(..)
, PDFTransDirection(..)
, PDFTransDimension(..)
, PDFTransDirection2(..)
, PDFDocumentInfo(..)
, PDFDocumentPageMode(..)
, PDFDocumentPageLayout(..)
, PDFViewerPreferences(..)
, standardDocInfo
, standardViewerPrefs
, Draw
, PDFXObject(drawXObject)
, PDFGlobals(..)
, withNewContext
, emptyDrawing
) where
#if !MIN_VERSION_base(4,8,0)
import Data.Monoid
#endif
import Graphics.PDF.LowLevel.Types
import Graphics.PDF.Draw
import Graphics.PDF.Pages
import Control.Monad.State
import qualified Data.IntMap as IM
import qualified Data.Map.Strict as M
import qualified Data.Text as T
standardDocInfo :: PDFDocumentInfo
standardDocInfo = PDFDocumentInfo T.empty T.empty UseNone SinglePage standardViewerPrefs True
createPDFXForm :: PDFFloat
-> PDFFloat
-> PDFFloat
-> PDFFloat
-> Draw a
-> PDF (PDFReference PDFXForm)
createPDFXForm xa ya xb yb d = let a' = do modifyStrict $ \s -> s {otherRsrcs = PDFDictionary. M.fromList $
[ (PDFName "Type",AnyPdfObject . PDFName $ "XObject")
, (PDFName "Subtype",AnyPdfObject . PDFName $ "Form")
, (PDFName "FormType",AnyPdfObject . PDFInteger $ 1)
, (PDFName "Matrix",AnyPdfObject . (map (AnyPdfObject . PDFInteger)) $ [1,0,0,1,0,0])
, (PDFName "BBox",AnyPdfObject . (map AnyPdfObject) $ [xa,ya,xb,yb])
]
}
d
in do
PDFReference s <- createContent a' Nothing
recordBound s (xb-xa) (yb-ya)
return (PDFReference s)
createANewPage :: Maybe PDFRect
-> PDF (Int,PDFPage)
createANewPage rect' = do
rect <- maybe (gets defaultRect) return rect'
pageref <- supply
pageContent <- createContent (return ()) (Just (PDFReference pageref :: PDFReference PDFPage))
let page = PDFPage Nothing rect pageContent Nothing Nothing Nothing []
return (pageref , page)
addPage :: Maybe PDFRect
-> PDF (PDFReference PDFPage)
addPage rect' = do
(pf,page) <- createANewPage rect'
let pageref = PDFReference pf
modifyStrict $ \s -> s {pages = recordPage pageref page (pages s), currentPage = Just pageref}
return pageref
addPageWithTransition :: Maybe PDFRect
-> Maybe PDFFloat
-> Maybe PDFTransition
-> PDF (PDFReference PDFPage)
addPageWithTransition rect' dur t = do
(pf,PDFPage a b c d _ _ pageAnnots) <- createANewPage rect'
let pageref = PDFReference pf
modifyStrict $ \s -> s {pages = recordPage pageref (PDFPage a b c d dur t pageAnnots) (pages s), currentPage = Just pageref}
return pageref
drawWithPage :: PDFReference PDFPage
-> Draw a
-> PDF a
drawWithPage page draw = do
lPages <- gets pages
lStreams <- gets streams
let thePage = findPage page lPages
case thePage of
Nothing -> error "Can't find the page to draw on it"
Just(PDFPage _ _ (PDFReference streamRef) _ _ _ _) -> do
let theContent = IM.lookup streamRef lStreams
case theContent of
Nothing -> error "Can't find a content for the page to draw on it"
Just (_,(oldState,oldW)) -> do
myBounds <- gets xobjectBound
let (a,state',w') = runDrawing draw (emptyEnvironment {streamId = streamRef, xobjectBoundD = myBounds}) oldState
modifyStrict $ \s -> s {streams = IM.insert streamRef (Just page,(state',mappend oldW w')) lStreams}
return a