summaryrefslogtreecommitdiff
path: root/src/Tex.hs
diff options
context:
space:
mode:
Diffstat (limited to 'src/Tex.hs')
-rw-r--r--src/Tex.hs72
1 files changed, 72 insertions, 0 deletions
diff --git a/src/Tex.hs b/src/Tex.hs
new file mode 100644
index 0000000..a247218
--- /dev/null
+++ b/src/Tex.hs
@@ -0,0 +1,72 @@
1module Tex
2 ( compileTex
3 ) where
4
5import System.IO (stdout, stderr, hPutStrLn, writeFile, readFile)
6import System.IO.Temp (withSystemTempDirectory)
7import System.Process (callProcess, readProcessWithExitCode)
8import System.Directory (copyFile, getCurrentDirectory, setCurrentDirectory)
9import System.FilePath (takeFileName, FilePath(..), (</>))
10import System.Exit (ExitCode(..))
11
12import Control.Monad (when)
13import Control.Exception (bracket, throwIO)
14import Data.Maybe (fromMaybe, listToMaybe)
15
16import Control.Monad.Writer.Strict (WriterT(..), execWriterT, tell)
17import Control.Monad.Trans (liftIO)
18
19import Control.DeepSeq (($!!))
20
21import Text.Regex.TDFA ((=~))
22
23instance Monoid ExitCode where
24 mempty = ExitSuccess
25 (ExitFailure a) `mappend` _ = ExitFailure a
26 ExitSuccess `mappend` x@(ExitFailure _) = x
27 ExitSuccess `mappend` ExitSuccess = ExitSuccess
28
29
30compileTex :: String -> IO (String, String)
31compileTex = withSystemTempDirectory "tex" . compileTex'
32
33compileTex' :: String -> FilePath -> IO (String, String)
34compileTex' input tmpDir = do
35 mapM_ (copyToTmp . ("provider/tex" </>)) [ "preview.dtx"
36 , "preview.ins"
37 ]
38 (exitCode, out, err) <- withCurrentDirectory tmpDir $ execWriterT $ do
39 run "latex" [ "-interaction=batchmode"
40 , "preview.ins"
41 ] ""
42 liftIO $ writeFile (tmpDir </> "image.tex") input
43 run "latex" [ {- "-interaction=batchmode"
44 , -} "image.tex"
45 ] ""
46 run "dvisvgm" [ "--exact"
47 , "--no-fonts"
48 , tmpDir </> "image.dvi"
49 ] ""
50 when (exitCode /= ExitSuccess) $ do
51 hPutStrLn stdout out
52 hPutStrLn stderr err
53 throwIO exitCode
54 (\x -> return $!! (x, extractAlignment err)) =<< (readFile $ tmpDir </> "image.svg")
55 where
56 copyToTmp fp = copyFile fp (tmpDir </> takeFileName fp)
57 run :: String -> [String] -> String -> WriterT (ExitCode, String, String) IO ()
58 run bin args stdin = tell =<< liftIO (readProcessWithExitCode bin args stdin)
59
60withCurrentDirectory :: FilePath -- ^ Directory to execute in
61 -> IO a -- ^ Action to be executed
62 -> IO a
63withCurrentDirectory dir action =
64 bracket getCurrentDirectory setCurrentDirectory $ \ _ -> do
65 setCurrentDirectory dir
66 action
67
68extractAlignment :: String -> String
69extractAlignment = fromMaybe "0pt" . extract . (=~ "depth=([^\\s]+)")
70 where
71 extract :: (String, String, String, [String]) -> Maybe String
72 extract (_, _, _, xs) = listToMaybe xs