{-# 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
standardDocInfo = Text
-> Text
-> PDFDocumentPageMode
-> PDFDocumentPageLayout
-> PDFViewerPreferences
-> Bool
-> PDFDocumentInfo
PDFDocumentInfo Text
T.empty Text
T.empty PDFDocumentPageMode
UseNone PDFDocumentPageLayout
SinglePage PDFViewerPreferences
standardViewerPrefs Bool
True
createPDFXForm :: PDFFloat
-> PDFFloat
-> PDFFloat
-> PDFFloat
-> Draw a
-> PDF (PDFReference PDFXForm)
createPDFXForm :: forall a.
PDFFloat
-> PDFFloat
-> PDFFloat
-> PDFFloat
-> Draw a
-> PDF (PDFReference PDFXForm)
createPDFXForm PDFFloat
xa PDFFloat
ya PDFFloat
xb PDFFloat
yb Draw a
d = let a' :: Draw a
a' = do forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modifyStrict forall a b. (a -> b) -> a -> b
$ \DrawState
s -> DrawState
s {otherRsrcs :: PDFDictionary
otherRsrcs = Map PDFName AnyPdfObject -> PDFDictionary
PDFDictionaryforall b c a. (b -> c) -> (a -> b) -> a -> c
. forall k a. Ord k => [(k, a)] -> Map k a
M.fromList forall a b. (a -> b) -> a -> b
$
[ (String -> PDFName
PDFName String
"Type",forall a. (PdfObject a, PdfLengthInfo a) => a -> AnyPdfObject
AnyPdfObject forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> PDFName
PDFName forall a b. (a -> b) -> a -> b
$ String
"XObject")
, (String -> PDFName
PDFName String
"Subtype",forall a. (PdfObject a, PdfLengthInfo a) => a -> AnyPdfObject
AnyPdfObject forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> PDFName
PDFName forall a b. (a -> b) -> a -> b
$ String
"Form")
, (String -> PDFName
PDFName String
"FormType",forall a. (PdfObject a, PdfLengthInfo a) => a -> AnyPdfObject
AnyPdfObject forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> PDFInteger
PDFInteger forall a b. (a -> b) -> a -> b
$ Int
1)
, (String -> PDFName
PDFName String
"Matrix",forall a. (PdfObject a, PdfLengthInfo a) => a -> AnyPdfObject
AnyPdfObject forall b c a. (b -> c) -> (a -> b) -> a -> c
. (forall a b. (a -> b) -> [a] -> [b]
map (forall a. (PdfObject a, PdfLengthInfo a) => a -> AnyPdfObject
AnyPdfObject forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> PDFInteger
PDFInteger)) forall a b. (a -> b) -> a -> b
$ [Int
1,Int
0,Int
0,Int
1,Int
0,Int
0])
, (String -> PDFName
PDFName String
"BBox",forall a. (PdfObject a, PdfLengthInfo a) => a -> AnyPdfObject
AnyPdfObject forall b c a. (b -> c) -> (a -> b) -> a -> c
. (forall a b. (a -> b) -> [a] -> [b]
map forall a. (PdfObject a, PdfLengthInfo a) => a -> AnyPdfObject
AnyPdfObject) forall a b. (a -> b) -> a -> b
$ [PDFFloat
xa,PDFFloat
ya,PDFFloat
xb,PDFFloat
yb])
]
}
Draw a
d
in do
PDFReference Int
s <- forall a.
Draw a
-> Maybe (PDFReference PDFPage) -> PDF (PDFReference PDFStream)
createContent Draw a
a' forall a. Maybe a
Nothing
Int -> PDFFloat -> PDFFloat -> PDF ()
recordBound Int
s (PDFFloat
xbforall a. Num a => a -> a -> a
-PDFFloat
xa) (PDFFloat
ybforall a. Num a => a -> a -> a
-PDFFloat
ya)
forall (m :: * -> *) a. Monad m => a -> m a
return (forall s. Int -> PDFReference s
PDFReference Int
s)
createANewPage :: Maybe PDFRect
-> PDF (Int,PDFPage)
createANewPage :: Maybe PDFRect -> PDF (Int, PDFPage)
createANewPage Maybe PDFRect
rect' = do
PDFRect
rect <- forall b a. b -> (a -> b) -> Maybe a -> b
maybe (forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets PdfState -> PDFRect
defaultRect) forall (m :: * -> *) a. Monad m => a -> m a
return Maybe PDFRect
rect'
Int
pageref <- PDF Int
supply
PDFReference PDFStream
pageContent <- forall a.
Draw a
-> Maybe (PDFReference PDFPage) -> PDF (PDFReference PDFStream)
createContent (forall (m :: * -> *) a. Monad m => a -> m a
return ()) (forall a. a -> Maybe a
Just (forall s. Int -> PDFReference s
PDFReference Int
pageref :: PDFReference PDFPage))
let page :: PDFPage
page = Maybe (PDFReference PDFPages)
-> PDFRect
-> PDFReference PDFStream
-> Maybe (PDFReference PDFResource)
-> Maybe PDFFloat
-> Maybe PDFTransition
-> [AnyPdfObject]
-> PDFPage
PDFPage forall a. Maybe a
Nothing PDFRect
rect PDFReference PDFStream
pageContent forall a. Maybe a
Nothing forall a. Maybe a
Nothing forall a. Maybe a
Nothing []
forall (m :: * -> *) a. Monad m => a -> m a
return (Int
pageref , PDFPage
page)
addPage :: Maybe PDFRect
-> PDF (PDFReference PDFPage)
addPage :: Maybe PDFRect -> PDF (PDFReference PDFPage)
addPage Maybe PDFRect
rect' = do
(Int
pf,PDFPage
page) <- Maybe PDFRect -> PDF (Int, PDFPage)
createANewPage Maybe PDFRect
rect'
let pageref :: PDFReference s
pageref = forall s. Int -> PDFReference s
PDFReference Int
pf
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modifyStrict forall a b. (a -> b) -> a -> b
$ \PdfState
s -> PdfState
s {pages :: Pages
pages = PDFReference PDFPage -> PDFPage -> Pages -> Pages
recordPage forall {s}. PDFReference s
pageref PDFPage
page (PdfState -> Pages
pages PdfState
s), currentPage :: Maybe (PDFReference PDFPage)
currentPage = forall a. a -> Maybe a
Just forall {s}. PDFReference s
pageref}
forall (m :: * -> *) a. Monad m => a -> m a
return forall {s}. PDFReference s
pageref
addPageWithTransition :: Maybe PDFRect
-> Maybe PDFFloat
-> Maybe PDFTransition
-> PDF (PDFReference PDFPage)
addPageWithTransition :: Maybe PDFRect
-> Maybe PDFFloat
-> Maybe PDFTransition
-> PDF (PDFReference PDFPage)
addPageWithTransition Maybe PDFRect
rect' Maybe PDFFloat
dur Maybe PDFTransition
t = do
(Int
pf,PDFPage Maybe (PDFReference PDFPages)
a PDFRect
b PDFReference PDFStream
c Maybe (PDFReference PDFResource)
d Maybe PDFFloat
_ Maybe PDFTransition
_ [AnyPdfObject]
pageAnnots) <- Maybe PDFRect -> PDF (Int, PDFPage)
createANewPage Maybe PDFRect
rect'
let pageref :: PDFReference s
pageref = forall s. Int -> PDFReference s
PDFReference Int
pf
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modifyStrict forall a b. (a -> b) -> a -> b
$ \PdfState
s -> PdfState
s {pages :: Pages
pages = PDFReference PDFPage -> PDFPage -> Pages -> Pages
recordPage forall {s}. PDFReference s
pageref (Maybe (PDFReference PDFPages)
-> PDFRect
-> PDFReference PDFStream
-> Maybe (PDFReference PDFResource)
-> Maybe PDFFloat
-> Maybe PDFTransition
-> [AnyPdfObject]
-> PDFPage
PDFPage Maybe (PDFReference PDFPages)
a PDFRect
b PDFReference PDFStream
c Maybe (PDFReference PDFResource)
d Maybe PDFFloat
dur Maybe PDFTransition
t [AnyPdfObject]
pageAnnots) (PdfState -> Pages
pages PdfState
s), currentPage :: Maybe (PDFReference PDFPage)
currentPage = forall a. a -> Maybe a
Just forall {s}. PDFReference s
pageref}
forall (m :: * -> *) a. Monad m => a -> m a
return forall {s}. PDFReference s
pageref
drawWithPage :: PDFReference PDFPage
-> Draw a
-> PDF a
drawWithPage :: forall a. PDFReference PDFPage -> Draw a -> PDF a
drawWithPage PDFReference PDFPage
page Draw a
draw = do
Pages
lPages <- forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets PdfState -> Pages
pages
IntMap (Maybe (PDFReference PDFPage), (DrawState, Builder))
lStreams <- forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets PdfState
-> IntMap (Maybe (PDFReference PDFPage), (DrawState, Builder))
streams
let thePage :: Maybe PDFPage
thePage = PDFReference PDFPage -> Pages -> Maybe PDFPage
findPage PDFReference PDFPage
page Pages
lPages
case Maybe PDFPage
thePage of
Maybe PDFPage
Nothing -> forall a. HasCallStack => String -> a
error String
"Can't find the page to draw on it"
Just(PDFPage Maybe (PDFReference PDFPages)
_ PDFRect
_ (PDFReference Int
streamRef) Maybe (PDFReference PDFResource)
_ Maybe PDFFloat
_ Maybe PDFTransition
_ [AnyPdfObject]
_) -> do
let theContent :: Maybe (Maybe (PDFReference PDFPage), (DrawState, Builder))
theContent = forall a. Int -> IntMap a -> Maybe a
IM.lookup Int
streamRef IntMap (Maybe (PDFReference PDFPage), (DrawState, Builder))
lStreams
case Maybe (Maybe (PDFReference PDFPage), (DrawState, Builder))
theContent of
Maybe (Maybe (PDFReference PDFPage), (DrawState, Builder))
Nothing -> forall a. HasCallStack => String -> a
error String
"Can't find a content for the page to draw on it"
Just (Maybe (PDFReference PDFPage)
_,(DrawState
oldState,Builder
oldW)) -> do
IntMap (PDFFloat, PDFFloat)
myBounds <- forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets PdfState -> IntMap (PDFFloat, PDFFloat)
xobjectBound
let (a
a,DrawState
state',Builder
w') = forall a.
Draw a -> DrawEnvironment -> DrawState -> (a, DrawState, Builder)
runDrawing Draw a
draw (DrawEnvironment
emptyEnvironment {streamId :: Int
streamId = Int
streamRef, xobjectBoundD :: IntMap (PDFFloat, PDFFloat)
xobjectBoundD = IntMap (PDFFloat, PDFFloat)
myBounds}) DrawState
oldState
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modifyStrict forall a b. (a -> b) -> a -> b
$ \PdfState
s -> PdfState
s {streams :: IntMap (Maybe (PDFReference PDFPage), (DrawState, Builder))
streams = forall a. Int -> a -> IntMap a -> IntMap a
IM.insert Int
streamRef (forall a. a -> Maybe a
Just PDFReference PDFPage
page,(DrawState
state',forall a. Monoid a => a -> a -> a
mappend Builder
oldW Builder
w')) IntMap (Maybe (PDFReference PDFPage), (DrawState, Builder))
lStreams}
forall (m :: * -> *) a. Monad m => a -> m a
return a
a