module Diagrams.Backend.Pdf.CmdLine
( defaultMain
, multipleMain
, renderDia'
, Pdf
) where
import Diagrams.Prelude hiding (width, height, interval)
import Diagrams.Backend.Pdf
import System.Console.CmdArgs.Implicit hiding (args)
import Prelude
import Data.List.Split
import System.Environment (getProgName)
import qualified Graphics.PDF as P
data DiagramOpts = DiagramOpts
{ width :: Maybe Int
, height :: Maybe Int
, output :: FilePath
, compressed :: Maybe Bool
, author :: Maybe String
}
deriving (Show, Data, Typeable)
diagramOpts :: String -> DiagramOpts
diagramOpts prog = DiagramOpts
{ width = def
&= typ "INT"
&= help "Desired width of the output image (default 400)"
, height = def
&= typ "INT"
&= help "Desired height of the output image (default 400)"
, output = def
&= typFile
&= help "Output file"
, compressed = def
&= typ "BOOL"
&= help "Compressed PDF file"
, author = def
&= typ "STRING"
&= help "Author of the document"
}
&= summary "Command-line diagram generation."
&= program prog
defaultMain :: Diagram Pdf R2 -> IO ()
defaultMain d = do
prog <- getProgName
opts <- cmdArgs (diagramOpts prog)
let sizeSpec = case (width opts, height opts) of
(Nothing, Nothing) -> Absolute
(Just wi, Nothing) -> Width (fromIntegral wi)
(Nothing, Just he) -> Height (fromIntegral he)
(Just wi, Just he) -> Dims (fromIntegral wi)
(fromIntegral he)
(w,h) = sizeFromSpec sizeSpec
theAuthor = maybe "diagrams-pdf" id (author opts)
compression = maybe False id (compressed opts)
docRect = P.PDFRect 0 0 (floor w) (floor h)
pdfOpts = PdfOptions sizeSpec
ifCanRender opts $ do
P.runPdf (output opts)
(P.standardDocInfo { P.author=P.toPDFString theAuthor, P.compressed = compression}) docRect $ do
page1 <- P.addPage Nothing
P.drawWithPage page1 $ renderDia' d pdfOpts
multipleMain :: [Diagram Pdf R2] -> IO ()
multipleMain d = do
prog <- getProgName
opts <- cmdArgs (diagramOpts prog)
let sizeSpec = case (width opts, height opts) of
(Nothing, Nothing) -> Absolute
(Just wi, Nothing) -> Width (fromIntegral wi)
(Nothing, Just he) -> Height (fromIntegral he)
(Just wi, Just he) -> Dims (fromIntegral wi)
(fromIntegral he)
(w,h) = sizeFromSpec sizeSpec
theAuthor = maybe "diagrams-pdf" id (author opts)
compression = maybe False id (compressed opts)
docRect = P.PDFRect 0 0 (floor w) (floor h)
pdfOpts = PdfOptions sizeSpec
createPage aDiag = do
page1 <- P.addPage Nothing
P.drawWithPage page1 $ renderDia' aDiag pdfOpts
ifCanRender opts $ do
P.runPdf (output opts)
(P.standardDocInfo { P.author=P.toPDFString theAuthor, P.compressed = compression}) docRect $ do
mapM_ createPage d
ifCanRender :: DiagramOpts -> IO () -> IO ()
ifCanRender opts action =
case splitOn "." (output opts) of
[""] -> putStrLn "No output file given."
ps | last ps `elem` ["pdf"] -> action
| otherwise -> putStrLn $ "Unknown file type: " ++ last ps
renderDia' :: Diagram Pdf R2
-> Options Pdf R2
-> P.Draw ()
renderDia' diag opts = do
let bd = boundingBox diag
(w,h) = sizeFromSpec (pdfsizeSpec opts)
rescaledD (Just (ll,ur)) =
let v = r2 . unp2 $ centroid [ll,ur]
(xa,ya) = unp2 ll
(xb,yb) = unp2 ur
ps = max (abs (xb xa)) (abs (yb ya))
sx = w / ps
sy = h / ps
pageCenter = r2 (w / 2.0, h/2.0)
in
translate pageCenter . scaleX sx . scaleY sy . translate (v) $ diag
rescaledD Nothing = diag
renderDia Pdf opts (rescaledD (getCorners bd))