summaryrefslogtreecommitdiff
path: root/src/Math.hs
blob: db01f755a1dd8bfae8cf84fabc84392901d435f4 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
module Math
       ( compileMath
       ) where

import System.IO (stdout, stderr, hPutStrLn, writeFile, readFile)
import System.IO.Temp (withSystemTempDirectory)
import System.Process (callProcess, readProcessWithExitCode)
import System.Directory (copyFile, getCurrentDirectory, setCurrentDirectory)
import System.FilePath (takeFileName, FilePath(..), (</>))
import System.Exit (ExitCode(..))

import Control.Monad (when)
import Control.Exception (bracket, throwIO)
import Data.Maybe (fromMaybe, listToMaybe)

import Control.Monad.Writer.Strict (WriterT(..), execWriterT, tell)
import Control.Monad.Trans (liftIO)

import Control.DeepSeq (($!!))

import Text.Regex.TDFA ((=~))

instance Monoid ExitCode where
  mempty = ExitSuccess
  (ExitFailure a) `mappend` _ = ExitFailure a
  ExitSuccess `mappend` x@(ExitFailure _) = x
  ExitSuccess `mappend` ExitSuccess = ExitSuccess
  

compileMath :: String -> IO (String, String)
compileMath = withSystemTempDirectory "math" . compileMath'

compileMath' :: String -> FilePath -> IO (String, String)
compileMath' input tmpDir = do
  mapM_ (copyToTmp . ("tex" </>)) [ "preamble.tex"
                                  , "preview.dtx"
                                  , "preview.ins"
                                  ]
  (exitCode, out, err) <- withCurrentDirectory tmpDir $ execWriterT $ do
    run "latex" [ "-interaction=batchmode"
                , "preview.ins"
                ] ""
    liftIO $ writeFile (tmpDir </> "image.tex") input
    run "latex" [ "-interaction=batchmode"
                , "image.tex"
                ] ""
    run "dvisvgm" [ "--exact"
                  , "--no-fonts"
                  , tmpDir </> "image.dvi"
                  ] ""
  when (exitCode /= ExitSuccess) $ do
    hPutStrLn stdout out
    hPutStrLn stderr err
    throwIO exitCode
  (\x -> return $!! (x, extractAlignment err)) =<< (readFile $ tmpDir </> "image.svg")
  where
    copyToTmp fp = copyFile fp (tmpDir </> takeFileName fp)
    run :: String -> [String] -> String -> WriterT (ExitCode, String, String) IO ()
    run bin args stdin = tell =<< liftIO (readProcessWithExitCode bin args stdin)

withCurrentDirectory :: FilePath  -- ^ Directory to execute in
                     -> IO a      -- ^ Action to be executed
                     -> IO a
withCurrentDirectory dir action =
  bracket getCurrentDirectory setCurrentDirectory $ \ _ -> do
    setCurrentDirectory dir
    action

extractAlignment :: String -> String
extractAlignment = fromMaybe "0pt" . extract . (=~ "depth=([^\\s]+)")
  where
    extract :: (String, String, String, [String]) -> Maybe String
    extract (_, _, _, xs) = listToMaybe xs