{-# LANGUAGE GADTs #-}
{-# LANGUAGE OverloadedStrings #-}
module Image.LaTeX.Render.Pandoc (
convertFormulaSvgInline,
convertFormulaSvgBlock,
convertFormulaSvgPandoc,
convertFormulaFilesInline,
convertFormulaFilesBlock,
convertFormulaFilesPandoc,
NameSupply,
newNameSupply,
PandocFormulaOptions(..),
ShrinkSize,
defaultPandocFormulaOptions,
hideError,
displayError,
convertFormulaSvgInlineWith,
convertFormulaSvgBlockWith,
convertFormulaSvgPandocWith,
convertFormulaFilesInlineWith,
convertFormulaFilesBlockWith,
convertFormulaFilesPandocWith,
) where
import Data.IORef (IORef, modifyIORef, newIORef, readIORef)
import Data.String (IsString (..))
import Numeric (showFFloat)
import System.FilePath ((<.>), (</>))
import Text.Pandoc.Definition (Block (..), Format (..), Inline (..), MathType (..), Pandoc, nullAttr)
import Text.Pandoc.Walk (walkM)
import qualified Data.Text as T
import Image.LaTeX.Render
data PandocFormulaOptions = PandocFormulaOptions
{ errorDisplay :: RenderError -> Inline
, formulaOptions :: Maybe MathType -> FormulaOptions
}
defaultPandocFormulaOptions :: PandocFormulaOptions
defaultPandocFormulaOptions = PandocFormulaOptions
{ errorDisplay = displayError
, formulaOptions = fopts
}
where
fopts (Just DisplayMath) = displaymath
fopts (Just InlineMath) = math
fopts Nothing = defaultFormulaOptions
type ShrinkSize = Int
convertFormulaSvgInline
:: EnvironmentOptions
-> PandocFormulaOptions
-> Inline -> IO Inline
convertFormulaSvgInline = convertFormulaSvgInlineWith . imageForFormula
convertFormulaSvgBlock
:: EnvironmentOptions
-> PandocFormulaOptions
-> Block -> IO Block
convertFormulaSvgBlock = convertFormulaSvgBlockWith . imageForFormula
convertFormulaSvgPandoc
:: EnvironmentOptions
-> PandocFormulaOptions
-> Pandoc -> IO Pandoc
convertFormulaSvgPandoc e = walkM . convertFormulaSvgBlock e
convertFormulaSvgBlockWith
:: (FormulaOptions -> Formula -> IO (Either RenderError SVG))
-> PandocFormulaOptions
-> Block -> IO Block
convertFormulaSvgBlockWith f o (RawBlock format s)
| format == Format "tex"
= do
res <- f (formulaOptions o Nothing) (toString s)
return $ Para $ singleton $ case res of
Left e -> errorDisplay o e
Right svg -> RawInline (Format "html") $ fromString $ alterForHTML svg
convertFormulaSvgBlockWith f o b = walkM (convertFormulaSvgInlineWith f o) b
convertFormulaSvgInlineWith
:: (FormulaOptions -> Formula -> IO (Either RenderError SVG))
-> PandocFormulaOptions
-> Inline -> IO Inline
convertFormulaSvgInlineWith f o (Math t s) = do
res <- f (formulaOptions o (Just t)) (toString s)
return $ case res of
Left e -> errorDisplay o e
Right svg -> RawInline (Format "html") $ fromString $ alterForHTML svg
convertFormulaSvgInlineWith _ _ x = return x
convertFormulaSvgPandocWith
:: (FormulaOptions -> Formula -> IO (Either RenderError SVG))
-> PandocFormulaOptions
-> Pandoc -> IO Pandoc
convertFormulaSvgPandocWith f = walkM . convertFormulaSvgBlockWith f
type NameSupply = IORef Int
newNameSupply :: IO NameSupply
newNameSupply = newIORef 0
convertFormulaFilesInlineWith
:: (FormulaOptions -> Formula -> IO (Either RenderError SVG))
-> NameSupply
-> FilePath
-> PandocFormulaOptions
-> Inline -> IO Inline
convertFormulaFilesInlineWith f ns bn o (Math t s) = f (formulaOptions o (Just t)) (toString s) >>= \res -> case res of
Left e -> return $ errorDisplay o e
Right svg -> makeSvgFile ns bn (Just t) svg
convertFormulaFilesInlineWith _ _ _ _ x = return x
makeSvgFile :: NameSupply -> FilePath -> Maybe MathType -> SVG -> IO Inline
makeSvgFile ns bn t svg = do
let baseline = getBaseline svg
fn <- readIORef ns
modifyIORef ns (+1)
let uri = bn </> show fn <.> "svg"
writeFile uri svg
let classArg = case t of
Nothing -> ""
Just InlineMath -> " class='inline-math'"
Just DisplayMath -> " class='display-math'"
return $ RawInline (Format "html") $ fromString $
"<img src=\"" ++ uri ++ "\"" ++ classArg ++
" style=\"margin:0; vertical-align:-" ++ showFFloat (Just 6) baseline "" ++ "pt;\"/>"
convertFormulaFilesBlockWith
:: (FormulaOptions -> Formula -> IO (Either RenderError SVG))
-> NameSupply
-> FilePath
-> PandocFormulaOptions
-> Block -> IO Block
convertFormulaFilesBlockWith f ns bn o (RawBlock format s)
| format == Format "tex"
= do
res <- f (formulaOptions o Nothing) (toString s)
case res of
Left e -> return $ Para $ singleton $ errorDisplay o e
Right svg -> fmap (Para . singleton) $ makeSvgFile ns bn Nothing svg
convertFormulaFilesBlockWith f ns bn o b = walkM (convertFormulaFilesInlineWith f ns bn o) b
convertFormulaFilesInline
:: EnvironmentOptions
-> NameSupply
-> FilePath
-> PandocFormulaOptions
-> Inline -> IO Inline
convertFormulaFilesInline = convertFormulaFilesInlineWith . imageForFormula
convertFormulaFilesBlock
:: EnvironmentOptions
-> NameSupply
-> FilePath
-> PandocFormulaOptions
-> Block -> IO Block
convertFormulaFilesBlock = convertFormulaFilesBlockWith . imageForFormula
convertFormulaFilesPandoc
:: EnvironmentOptions
-> NameSupply
-> FilePath
-> PandocFormulaOptions
-> Pandoc -> IO Pandoc
convertFormulaFilesPandoc eo ns fp = walkM . convertFormulaFilesInline eo ns fp
convertFormulaFilesPandocWith
:: (FormulaOptions -> Formula -> IO (Either RenderError SVG))
-> NameSupply
-> FilePath
-> PandocFormulaOptions
-> Pandoc -> IO Pandoc
convertFormulaFilesPandocWith x y a = walkM . convertFormulaFilesInlineWith x y a
hideError :: RenderError -> Inline
hideError = const $ Str blank
where
blank = "Error"
displayError :: RenderError -> Inline
displayError (LaTeXFailure str) = pandocError [Str "LaTeX failed:", LineBreak, Code nullAttr $ fromString str]
displayError (DVISVGMFailure str) = pandocError [Str "DVIPS failed:", LineBreak, Code nullAttr $ fromString str]
displayError (IOException e) = pandocError [Str "IO Exception:", LineBreak, Code nullAttr $ fromString $ show e]
pandocError :: [Inline] -> Inline
pandocError = Strong . (Emph [Str "Error:"] :)
class IsString s => ToString s where
toString :: s -> String
instance Char ~ c => ToString [c] where
toString = id
instance ToString T.Text where
toString = T.unpack
singleton :: a -> [a]
singleton = return