module Diagrams.Backend.PGF.CmdLine
(
mainWith
, defaultMain
, mainWithSurf
, onlineMain
, onlineMainWithSurf
, multiMain
, module Diagrams.Backend.PGF
) where
import Data.ByteString.Builder
import Options.Applicative as OP
import System.IO (stdout)
import Diagrams.Backend.CmdLine
import Diagrams.Prelude hiding (height, interval, output,
width)
import Diagrams.Backend.PGF
import Diagrams.Backend.PGF.Surface
data PGFCmdLineOpts = PGFCmdLineOpts
{ _cmdStandalone :: Bool
, _cmdReadable :: Bool
}
makeLenses ''PGFCmdLineOpts
instance Parseable PGFCmdLineOpts where
parser = PGFCmdLineOpts
<$> switch
( long "standalone"
<> short 'a'
<> help "Produce standalone .tex output"
)
<*> switch
( long "readable"
<> short 'r'
<> help "Indent lines"
)
instance ToResult d => ToResult (OnlineTex d) where
type Args (OnlineTex d) = (Surface, Args d)
type ResultOf (OnlineTex d) = IO (ResultOf d)
toResult d (surf, args) = flip toResult args <$> surfOnlineTexIO surf d
defaultMain :: Diagram PGF -> IO ()
defaultMain = mainWith
mainWithSurf :: Surface -> Diagram PGF -> IO ()
mainWithSurf = curry mainWith
onlineMain :: OnlineTex (Diagram PGF) -> IO ()
onlineMain = mainWith
onlineMainWithSurf :: Surface -> OnlineTex (Diagram PGF) -> IO ()
onlineMainWithSurf = curry mainWith
instance TypeableFloat n => Mainable (QDiagram PGF V2 n Any) where
type MainOpts (QDiagram PGF V2 n Any) =
(DiagramOpts, DiagramLoopOpts, PGFCmdLineOpts, TexFormat)
mainRender (diaOpts, loopOpts, pgfOpts, format) d = do
chooseRender diaOpts pgfOpts (formatToSurf format) d
defaultLoopRender loopOpts
instance TypeableFloat n => Mainable (Surface, QDiagram PGF V2 n Any) where
type MainOpts (Surface, QDiagram PGF V2 n Any) =
(DiagramOpts, DiagramLoopOpts, PGFCmdLineOpts)
mainRender (diaOpts, loopOpts, pgfOpts) (surf,d) = do
chooseRender diaOpts pgfOpts surf d
defaultLoopRender loopOpts
instance TypeableFloat n => Mainable (OnlineTex (QDiagram PGF V2 n Any)) where
type MainOpts (OnlineTex (QDiagram PGF V2 n Any))
= (DiagramOpts, DiagramLoopOpts, PGFCmdLineOpts, TexFormat)
mainRender (diaOpts, loopOpts, pgfOpts, format) d = do
chooseOnlineRender diaOpts pgfOpts (formatToSurf format) d
defaultLoopRender loopOpts
instance TypeableFloat n => Mainable (Surface, OnlineTex (QDiagram PGF V2 n Any)) where
type MainOpts (Surface, OnlineTex (QDiagram PGF V2 n Any))
= (DiagramOpts, DiagramLoopOpts, PGFCmdLineOpts)
mainRender (diaOpts, loopOpts, pgfOpts) (surf, d) = do
chooseOnlineRender diaOpts pgfOpts surf d
defaultLoopRender loopOpts
formatToSurf :: TexFormat -> Surface
formatToSurf format = case format of
LaTeX -> latexSurface
ConTeXt -> contextSurface
PlainTeX -> plaintexSurface
cmdLineOpts :: TypeableFloat n
=> DiagramOpts -> Surface -> PGFCmdLineOpts -> Options PGF V2 n
cmdLineOpts opts surf pgf
= def & surface .~ surf
& sizeSpec .~ sz
& readable .~ pgf^.cmdReadable
& standalone .~ pgf^.cmdStandalone
where
sz = fromIntegral <$> mkSizeSpec2D (opts^.width) (opts^.height)
chooseRender :: TypeableFloat n
=> DiagramOpts -> PGFCmdLineOpts -> Surface -> QDiagram PGF V2 n Any -> IO ()
chooseRender diaOpts pgfOpts surf d =
case diaOpts^.output of
"" -> hPutBuilder stdout $ renderDia PGF opts d
out -> renderPGF' out opts d
where
opts = cmdLineOpts diaOpts surf pgfOpts
chooseOnlineRender :: TypeableFloat n
=> DiagramOpts -> PGFCmdLineOpts -> Surface -> OnlineTex (QDiagram PGF V2 n Any) -> IO ()
chooseOnlineRender diaOpts pgfOpts surf d =
case diaOpts^.output of
"" -> surfOnlineTexIO surf d >>= hPutBuilder stdout . renderDia PGF opts
out -> renderOnlinePGF' out opts d
where
opts = cmdLineOpts diaOpts surf pgfOpts
multiMain :: [(String, Diagram PGF)] -> IO ()
multiMain = mainWith
instance TypeableFloat n => Mainable [(String,QDiagram PGF V2 n Any)] where
type MainOpts [(String,QDiagram PGF V2 n Any)]
= (MainOpts (QDiagram PGF V2 n Any), DiagramMultiOpts)
mainRender = defaultMultiMainRender
instance Parseable TexFormat where
parser = OP.option (eitherReader parseFormat)
$ short 'f'
<> long "format"
<> help "l for LaTeX, c for ConTeXt, p for plain TeX"
<> metavar "FORMAT"
<> OP.value LaTeX
<> showDefault
parseFormat :: String -> Either String TexFormat
parseFormat ('l':_) = Right LaTeX
parseFormat ('c':_) = Right ConTeXt
parseFormat ('p':_) = Right PlainTeX
parseFormat ('t':_) = Right PlainTeX
parseFormat x = Left $ "Unknown format" ++ x