From 5c4377102f442208d844a3d42aa23a0d074b7257 Mon Sep 17 00:00:00 2001
From: Gregor Kleen <gkleen@yggdrasil.li>
Date: Wed, 3 Feb 2016 18:23:10 +0100
Subject: Fixed tex \end fuckup

---
 src/Site.hs |  7 +++++--
 src/Tex.hs  | 10 +++++++---
 2 files changed, 12 insertions(+), 5 deletions(-)

(limited to 'src')

diff --git a/src/Site.hs b/src/Site.hs
index d3ac76d..03b6e16 100644
--- a/src/Site.hs
+++ b/src/Site.hs
@@ -170,7 +170,7 @@ getTex pattern makeId = do
       getTex' :: FilePath -> Rules [String]
       getTex' path = preprocess . fmap concat $ (\x -> [query extractTex, query extractTex'] <*> pure x) `liftM` readPandoc' path
       extractTex :: Inline -> [String]
-      extractTex (Math _ str) = ["\\(" ++ str ++ "\\)"]
+      extractTex (Math _ str) = [wrapMath str]
       extractTex (RawInline "latex" str) = [str]
       extractTex _ = []
       extractTex' :: Block -> [String]
@@ -181,6 +181,9 @@ getTex pattern makeId = do
       mergeGroups' :: [([Identifier], String)] -> ([Identifier], String)
       mergeGroups' xs@((_, str):_) = (concatMap fst xs, str)
 
+wrapMath :: String -> String
+wrapMath str = "\\(" ++ str ++ "\\)"
+
 readPandoc' :: FilePath -> IO Pandoc
 readPandoc' path = readFile path >>= either fail return . result'
   where
@@ -211,7 +214,7 @@ texTransform :: Pandoc -> Compiler Pandoc
 texTransform = walkM texTransformInline <=< walkM texTransformBlock
   where
     texTransformInline :: Inline -> Compiler Inline
-    texTransformInline (Math mathType tex) = (\html -> Span ("", [classOf mathType], []) [RawInline "html" html]) <$> texTransform' ("\\(" ++ tex ++ "\\)")
+    texTransformInline (Math mathType tex) = (\html -> Span ("", [classOf mathType], []) [RawInline "html" html]) <$> texTransform' (wrapMath tex)
     texTransformInline (RawInline "latex" tex) = (\html -> Span ("", [], []) [RawInline "html" html]) <$> texTransform' tex
     texTransformInline x = return x
     texTransformBlock :: Block -> Compiler Block
diff --git a/src/Tex.hs b/src/Tex.hs
index a247218..5d347b9 100644
--- a/src/Tex.hs
+++ b/src/Tex.hs
@@ -2,10 +2,10 @@ module Tex
        ( compileTex
        ) where
 
-import System.IO (stdout, stderr, hPutStrLn, writeFile, readFile)
-import System.IO.Temp (withSystemTempDirectory)
+import System.IO (stdout, stderr, hPutStrLn, writeFile, readFile, hClose)
+import System.IO.Temp (withSystemTempDirectory, openTempFile)
 import System.Process (callProcess, readProcessWithExitCode)
-import System.Directory (copyFile, getCurrentDirectory, setCurrentDirectory)
+import System.Directory (copyFile, getCurrentDirectory, setCurrentDirectory, getTemporaryDirectory)
 import System.FilePath (takeFileName, FilePath(..), (</>))
 import System.Exit (ExitCode(..))
 
@@ -50,6 +50,10 @@ compileTex' input tmpDir = do
   when (exitCode /= ExitSuccess) $ do
     hPutStrLn stdout out
     hPutStrLn stderr err
+    (srcF, srcH) <- flip openTempFile "source.tex" =<< getTemporaryDirectory
+    hPutStrLn srcH input
+    hClose srcH
+    hPutStrLn stdout $ "Tex source saved to " ++ srcF
     throwIO exitCode
   (\x -> return $!! (x, extractAlignment err)) =<< (readFile $ tmpDir </> "image.svg")
   where
-- 
cgit v1.2.3