module Hakyll.Contrib.LaTeX (
initFormulaCompilerSVG,
initFormulaCompilerSVGPure,
CacheSize,
compileFormulaeSVG,
) where
import Data.Char (isSpace)
import Hakyll.Core.Compiler (Compiler, unsafeCompiler)
import Text.Pandoc.Definition (Pandoc)
import Image.LaTeX.Render
import Image.LaTeX.Render.Pandoc
import qualified Data.Cache.LRU.IO as LRU
type CacheSize = Integer
initFormulaCompilerSVG
:: CacheSize
-> EnvironmentOptions
-> IO (PandocFormulaOptions -> Pandoc -> Compiler Pandoc)
initFormulaCompilerSVG cs eo = do
mImageForFormula <- curry <$> memoizeLru (Just cs) (uncurry drawFormula)
let eachFormula x y = do
putStrLn $ " formula (" ++ environment x ++ ") \"" ++ equationPreview y ++ "\""
mImageForFormula x y
return $ \fo -> unsafeCompiler . convertAllFormulaeSVGWith eachFormula fo
where
drawFormula x y = do
putStrLn " drawing..."
imageForFormula eo x y
initFormulaCompilerSVGPure
:: EnvironmentOptions
-> PandocFormulaOptions -> Pandoc -> Compiler Pandoc
initFormulaCompilerSVGPure eo fo pandoc = do
let mImageForFormula = drawFormula
let eachFormula x y = do
putStrLn $ " formula (" ++ environment x ++ ") \"" ++ equationPreview y ++ "\""
mImageForFormula x y
unsafeCompiler (convertAllFormulaeSVGWith eachFormula fo pandoc)
where
drawFormula x y = do
putStrLn " drawing..."
imageForFormula eo x y
compileFormulaeSVG
:: EnvironmentOptions
-> PandocFormulaOptions
-> Pandoc -> Compiler Pandoc
compileFormulaeSVG eo po =
let eachFormula x y = do
putStrLn $ " formula (" ++ environment x ++ ") \"" ++ equationPreview y ++ "\""
putStrLn " drawing..."
imageForFormula eo x y
in unsafeCompiler . convertAllFormulaeSVGWith eachFormula po
equationPreview :: String -> String
equationPreview x'
| length x <= 16 = x
| otherwise = take 16 $ filter (/= '\n') x ++ "..."
where
x = dropWhile isSpace x'
memoizeLru :: Ord a => Maybe Integer -> (a -> IO b) -> IO (a -> IO b)
memoizeLru msize action = do
lru <- LRU.newAtomicLRU msize
return $ \arg -> do
mret <- LRU.lookup arg lru
case mret of
Just ret -> return ret
Nothing -> do
ret <- action arg
LRU.insert arg ret lru
return ret