2016-12-03 16:15:13 +01:00
|
|
|
module Text.Pandoc.Writers.Math
|
|
|
|
( texMathToInlines
|
|
|
|
, convertMath
|
|
|
|
)
|
|
|
|
where
|
|
|
|
|
|
|
|
import Text.Pandoc.Class
|
|
|
|
import Text.Pandoc.Definition
|
2017-02-10 23:59:47 +01:00
|
|
|
import Text.Pandoc.Logging
|
2016-12-03 16:15:13 +01:00
|
|
|
import Text.TeXMath (Exp, writePandoc, DisplayType(..), readTeX)
|
|
|
|
|
|
|
|
-- | Converts a raw TeX math formula to a list of 'Pandoc' inlines.
|
|
|
|
-- Defaults to raw formula between @$@ or @$$@ characters if entire formula
|
|
|
|
-- can't be converted.
|
|
|
|
texMathToInlines :: PandocMonad m
|
|
|
|
=> MathType
|
|
|
|
-> String -- ^ String to parse (assumes @'\n'@ line endings)
|
|
|
|
-> m [Inline]
|
|
|
|
texMathToInlines mt inp = do
|
|
|
|
res <- convertMath writePandoc mt inp
|
|
|
|
case res of
|
|
|
|
Right (Just ils) -> return ils
|
2016-12-03 16:30:47 +01:00
|
|
|
Right (Nothing) -> do
|
2017-02-10 23:59:47 +01:00
|
|
|
report $ CouldNotConvertTeXMath inp ""
|
2016-12-03 16:30:47 +01:00
|
|
|
return [mkFallback mt inp]
|
2016-12-03 16:15:13 +01:00
|
|
|
Left il -> return [il]
|
|
|
|
|
|
|
|
mkFallback :: MathType -> String -> Inline
|
|
|
|
mkFallback mt str = Str (delim ++ str ++ delim)
|
|
|
|
where delim = case mt of
|
|
|
|
DisplayMath -> "$$"
|
|
|
|
InlineMath -> "$"
|
|
|
|
|
|
|
|
-- | Converts a raw TeX math formula using a writer function,
|
|
|
|
-- issuing a warning and producing a fallback (a raw string)
|
|
|
|
-- on failure.
|
|
|
|
convertMath :: PandocMonad m
|
|
|
|
=> (DisplayType -> [Exp] -> a) -> MathType -> String
|
|
|
|
-> m (Either Inline a)
|
|
|
|
convertMath writer mt str = do
|
|
|
|
case writer dt <$> readTeX str of
|
|
|
|
Right r -> return (Right r)
|
|
|
|
Left e -> do
|
2017-02-10 23:59:47 +01:00
|
|
|
report $ CouldNotConvertTeXMath str e
|
2016-12-03 16:15:13 +01:00
|
|
|
return (Left $ mkFallback mt str)
|
|
|
|
where dt = case mt of
|
|
|
|
DisplayMath -> DisplayBlock
|
|
|
|
InlineMath -> DisplayInline
|
|
|
|
|