summaryrefslogtreecommitdiff
path: root/src
diff options
context:
space:
mode:
Diffstat (limited to 'src')
-rw-r--r--src/Math.hs46
-rw-r--r--src/Site.hs9
2 files changed, 53 insertions, 2 deletions
diff --git a/src/Math.hs b/src/Math.hs
new file mode 100644
index 0000000..e927fdd
--- /dev/null
+++ b/src/Math.hs
@@ -0,0 +1,46 @@
1module Math
2 ( compileMath
3 ) where
4
5import System.IO.Temp (withSystemTempDirectory)
6import System.Process (callProcess)
7import System.Directory (copyFile, getCurrentDirectory, setCurrentDirectory)
8import System.FilePath (takeFileName, FilePath(..), (</>))
9
10import Control.Monad
11import Control.Exception (bracket)
12
13import Control.DeepSeq (($!!))
14
15compileMath :: String -> IO String
16compileMath = withSystemTempDirectory "math" . compileMath'
17
18compileMath' :: String -> FilePath -> IO String
19compileMath' input tmpDir = do
20 mapM_ (copyToTmp . ("tex" </>)) [ "preamble.tex"
21 , "preview.dtx"
22 , "preview.ins"
23 ]
24 withCurrentDirectory tmpDir $ do
25 callProcess "latex" [ "-interaction=batchmode"
26 , "preview.ins"
27 ]
28 writeFile (tmpDir </> "image.tex") input
29 callProcess "latex" [ "-interaction=batchmode"
30 , "image.tex"
31 ]
32 callProcess "dvisvgm" [ "--exact"
33 , "--no-fonts"
34 , tmpDir </> "image.dvi"
35 ]
36 (\x -> return $!! x) =<< (readFile $ tmpDir </> "image.svg")
37 where
38 copyToTmp fp = copyFile fp (tmpDir </> takeFileName fp)
39
40withCurrentDirectory :: FilePath -- ^ Directory to execute in
41 -> IO a -- ^ Action to be executed
42 -> IO a
43withCurrentDirectory dir action =
44 bracket getCurrentDirectory setCurrentDirectory $ \ _ -> do
45 setCurrentDirectory dir
46 action
diff --git a/src/Site.hs b/src/Site.hs
index 1bda7ec..e821322 100644
--- a/src/Site.hs
+++ b/src/Site.hs
@@ -20,9 +20,12 @@ import Control.Applicative (Alternative(..), Applicative(..))
20import qualified Crypto.Hash.SHA256 as SHA256 (hash) 20import qualified Crypto.Hash.SHA256 as SHA256 (hash)
21import qualified Data.ByteString.Char8 as CBS 21import qualified Data.ByteString.Char8 as CBS
22import Data.Hex 22import Data.Hex
23import Data.Char (toLower)
23 24
24import System.FilePath (takeBaseName, (</>), (<.>)) 25import System.FilePath (takeBaseName, (</>), (<.>))
25 26
27import Math (compileMath)
28
26main :: IO () 29main :: IO ()
27main = hakyllWith config $ do 30main = hakyllWith config $ do
28 match "templates/*" $ compile templateCompiler 31 match "templates/*" $ compile templateCompiler
@@ -45,7 +48,9 @@ main = hakyllWith config $ do
45 create [mathTranslation' mathStr] $ do 48 create [mathTranslation' mathStr] $ do
46 route idRoute 49 route idRoute
47 compile $ do 50 compile $ do
48 makeItem $ mathStr 51 makeItem mathStr
52 >>= loadAndApplyTemplate "templates/math.tex" defaultContext
53 >>= withItemBody (unsafeCompiler . compileMath)
49 54
50 tags <- buildTags "posts/*" tagTranslation' >>= addTag "All Posts" "posts/*" 55 tags <- buildTags "posts/*" tagTranslation' >>= addTag "All Posts" "posts/*"
51 56
@@ -139,7 +144,7 @@ tagTranslation = mapMaybe charTrans
139 | otherwise = Nothing 144 | otherwise = Nothing
140 145
141mathTranslation' :: String -> Identifier 146mathTranslation' :: String -> Identifier
142mathTranslation' = fromCapture "math/*.svg" . CBS.unpack . hex . SHA256.hash . CBS.pack 147mathTranslation' = fromCapture "math/*.svg" . map toLower . CBS.unpack . hex . SHA256.hash . CBS.pack
143 148
144addTag :: MonadMetadata m => String -> Pattern -> Tags -> m Tags 149addTag :: MonadMetadata m => String -> Pattern -> Tags -> m Tags
145addTag name pattern tags = do 150addTag name pattern tags = do