module Diagrams.Backend.PGF.Surface
(
Surface(..)
, TexFormat(..)
, surfOnlineTex
, surfOnlineTexIO
, latexSurface
, contextSurface
, plaintexSurface
, sampleSurfaceOutput
, texFormat
, command
, arguments
, pageSize
, preamble
, beginDoc
, endDoc
) where
import Data.ByteString.Builder
import Data.Hashable (Hashable (..))
import Data.Typeable (Typeable)
import System.IO.Unsafe
import System.Texrunner.Online
import Diagrams.Prelude
import Prelude
data TexFormat = LaTeX | ConTeXt | PlainTeX
deriving (Show, Read, Eq, Typeable)
data Surface = Surface
{ _texFormat :: TexFormat
, _command :: String
, _arguments :: [String]
, _pageSize :: Maybe (V2 Int -> String)
, _preamble :: String
, _beginDoc :: String
, _endDoc :: String
}
makeLensesWith (lensRules & generateSignatures .~ False) ''Surface
texFormat :: Lens' Surface TexFormat
command :: Lens' Surface String
arguments :: Lens' Surface [String]
preamble :: Lens' Surface String
pageSize :: Lens' Surface (Maybe (V2 Int -> String))
beginDoc :: Lens' Surface String
endDoc :: Lens' Surface String
latexSurface :: Surface
latexSurface = Surface
{ _texFormat = LaTeX
, _command = "pdflatex"
, _arguments = []
, _pageSize = Just $ \(V2 w h) ->
"\\pdfpagewidth=" ++ show w ++ "bp\n"
++ "\\pdfpageheight=" ++ show h ++ "bp\n"
++ "\\textheight=" ++ show h ++ "bp\n"
++ "\\pdfhorigin=-76.6bp\n"
++ "\\pdfvorigin=-52.8bp"
, _preamble = "\\documentclass{article}\n"
++ "\\usepackage{pgfcore}\n"
++ "\\pagenumbering{gobble}"
, _beginDoc = "\\begin{document}"
, _endDoc = "\\end{document}"
}
contextSurface :: Surface
contextSurface = Surface
{ _texFormat = ConTeXt
, _command = "context"
, _arguments = ["--pipe", "--once"]
, _pageSize = Just $ \(V2 w h) ->
"\\definepapersize[diagram][width="++ show w ++"bp,height="++ show h ++"bp]\n"
++ "\\setuppapersize[diagram][diagram]\n"
++ "\\setuplayout\n"
++ " [ topspace=0bp\n"
++ " , backspace=0bp\n"
++ " , header=0bp\n"
++ " , footer=0bp\n"
++ " , width=" ++ show w ++ "bp\n"
++ " , height=" ++ show h ++ "bp\n"
++ " ]"
, _preamble = "\\usemodule[pgf]\n"
++ "\\setuppagenumbering[location=]"
, _beginDoc = "\\starttext"
, _endDoc = "\\stoptext"
}
plaintexSurface :: Surface
plaintexSurface = Surface
{ _texFormat = PlainTeX
, _command = "pdftex"
, _arguments = []
, _pageSize = Just $ \(V2 w h) ->
"\\pdfpagewidth=" ++ show w ++ "bp\n"
++ "\\pdfpageheight=" ++ show h ++ "bp\n"
++ "\\pdfhorigin=-20bp\n"
++ "\\pdfvorigin=0bp"
, _preamble = "\\input eplain\n"
++ "\\beginpackages\n\\usepackage{color}\n\\endpackages\n"
++ "\\input pgfcore\n"
++ "\\def\\frac#1#2{{\\begingroup #1\\endgroup\\over #2}}"
++ "\\nopagenumbers"
, _beginDoc = ""
, _endDoc = "\\bye"
}
instance Default Surface where
def = latexSurface
sampleSurfaceOutput :: Surface -> String
sampleSurfaceOutput surf = unlines
[ "command: " ++ surf ^. command ++ " " ++ unwords (surf ^. arguments)
, "\n% preamble"
, surf ^. preamble
, "\n% pageSize"
, view _Just $ surf ^. pageSize <*> Just (V2 100 80)
, "\n% beginDoc"
, surf ^. beginDoc
, "\n<" ++ show (surf ^. texFormat) ++ " pgf code>"
, "\n% endDoc"
, surf ^. endDoc
]
surfOnlineTex :: Surface -> OnlineTex a -> a
surfOnlineTex surf a = unsafePerformIO (surfOnlineTexIO surf a)
surfOnlineTexIO :: Surface -> OnlineTex a -> IO a
surfOnlineTexIO surf = runOnlineTex (surf^.command) (surf^.arguments) begin
where
begin = view strict . toLazyByteString . stringUtf8
$ surf ^. (preamble <> beginDoc)
instance Hashable TexFormat where
hashWithSalt s LaTeX = s `hashWithSalt` (1::Int)
hashWithSalt s ConTeXt = s `hashWithSalt` (2::Int)
hashWithSalt s PlainTeX = s `hashWithSalt` (3::Int)
instance Hashable Surface where
hashWithSalt s (Surface tf cm ar ps p bd ed)
= s `hashWithSalt`
tf `hashWithSalt`
cm `hashWithSalt`
ar `hashWithSalt`
ps <*> Just (V2 1 2) `hashWithSalt`
p `hashWithSalt`
bd `hashWithSalt`
ed