aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Writers/Math.hs
diff options
context:
space:
mode:
Diffstat (limited to 'src/Text/Pandoc/Writers/Math.hs')
-rw-r--r--src/Text/Pandoc/Writers/Math.hs10
1 files changed, 6 insertions, 4 deletions
diff --git a/src/Text/Pandoc/Writers/Math.hs b/src/Text/Pandoc/Writers/Math.hs
index 3905a3abc..feb4b6dea 100644
--- a/src/Text/Pandoc/Writers/Math.hs
+++ b/src/Text/Pandoc/Writers/Math.hs
@@ -1,4 +1,5 @@
{-# LANGUAGE NoImplicitPrelude #-}
+{-# LANGUAGE OverloadedStrings #-}
module Text.Pandoc.Writers.Math
( texMathToInlines
, convertMath
@@ -8,6 +9,7 @@ module Text.Pandoc.Writers.Math
where
import Prelude
+import qualified Data.Text as T
import Text.Pandoc.Class
import Text.Pandoc.Definition
import Text.Pandoc.Logging
@@ -19,7 +21,7 @@ import Text.Pandoc.Options (defaultMathJaxURL, defaultKaTeXURL)
-- can't be converted.
texMathToInlines :: PandocMonad m
=> MathType
- -> String -- ^ String to parse (assumes @'\n'@ line endings)
+ -> T.Text -- ^ String to parse (assumes @'\n'@ line endings)
-> m [Inline]
texMathToInlines mt inp = do
res <- convertMath writePandoc mt inp
@@ -30,8 +32,8 @@ texMathToInlines mt inp = do
return [mkFallback mt inp]
Left il -> return [il]
-mkFallback :: MathType -> String -> Inline
-mkFallback mt str = Str (delim ++ str ++ delim)
+mkFallback :: MathType -> T.Text -> Inline
+mkFallback mt str = Str (delim <> str <> delim)
where delim = case mt of
DisplayMath -> "$$"
InlineMath -> "$"
@@ -40,7 +42,7 @@ mkFallback mt str = Str (delim ++ str ++ delim)
-- issuing a warning and producing a fallback (a raw string)
-- on failure.
convertMath :: PandocMonad m
- => (DisplayType -> [Exp] -> a) -> MathType -> String
+ => (DisplayType -> [Exp] -> a) -> MathType -> T.Text
-> m (Either Inline a)
convertMath writer mt str =
case writer dt <$> readTeX str of