Renamed readTeXMath' to avoid name conflict with texmath 0.6.7

Also removed deprecated readTeXMath.
This commit is contained in:
Matthew Pickering 2014-07-19 18:10:51 +01:00
parent fe6b4e532d
commit e7d8039969
9 changed files with 17 additions and 26 deletions

View file

@ -27,7 +27,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
Conversion of TeX math to a list of 'Pandoc' inline elements.
-}
module Text.Pandoc.Readers.TeXMath ( readTeXMath, readTeXMath' ) where
module Text.Pandoc.Readers.TeXMath ( texMathToInlines ) where
import Text.Pandoc.Definition
import Text.TeXMath
@ -35,22 +35,13 @@ import Text.TeXMath
-- | 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.
readTeXMath' :: MathType
texMathToInlines :: MathType
-> String -- ^ String to parse (assumes @'\n'@ line endings)
-> [Inline]
readTeXMath' mt inp = case texMathToPandoc dt inp of
texMathToInlines mt inp = case texMathToPandoc dt inp of
Left _ -> [Str (delim ++ inp ++ delim)]
Right res -> res
where (dt, delim) = case mt of
DisplayMath -> (DisplayBlock, "$$")
InlineMath -> (DisplayInline, "$")
{-# DEPRECATED readTeXMath "Use readTeXMath' from Text.Pandoc.JSON instead" #-}
-- | Converts a raw TeX math formula to a list of 'Pandoc' inlines.
-- Defaults to raw formula between @$@ characters if entire formula
-- can't be converted. (This is provided for backwards compatibility;
-- it is better to use @readTeXMath'@, which properly distinguishes
-- between display and inline math.)
readTeXMath :: String -- ^ String to parse (assumes @'\n'@ line endings)
-> [Inline]
readTeXMath = readTeXMath' InlineMath

View file

@ -299,8 +299,8 @@ inlineToDocbook opts (Math t str)
$ fixNS
$ removeAttr r
Left _ -> inlinesToDocbook opts
$ readTeXMath' t str
| otherwise = inlinesToDocbook opts $ readTeXMath' t str
$ texMathToInlines t str
| otherwise = inlinesToDocbook opts $ texMathToInlines t str
where (dt, tagtype) = case t of
InlineMath -> (DisplayInline,"inlineequation")
DisplayMath -> (DisplayBlock,"informalequation")

View file

@ -756,7 +756,7 @@ inlineToOpenXML opts (Math mathType str) = do
else DisplayInline
case texMathToOMML displayType str of
Right r -> return [r]
Left _ -> inlinesToOpenXML opts (readTeXMath' mathType str)
Left _ -> inlinesToOpenXML opts (texMathToInlines mathType str)
inlineToOpenXML opts (Cite _ lst) = inlinesToOpenXML opts lst
inlineToOpenXML opts (Code attrs str) =
withTextProp (rStyle "VerbatimChar")

View file

@ -704,14 +704,14 @@ inlineToHtml opts inline =
Right r -> return $ preEscapedString $
ppcElement conf r
Left _ -> inlineListToHtml opts
(readTeXMath' t str) >>= return .
(texMathToInlines t str) >>= return .
(H.span ! A.class_ "math")
MathJax _ -> return $ H.span ! A.class_ "math" $ toHtml $
case t of
InlineMath -> "\\(" ++ str ++ "\\)"
DisplayMath -> "\\[" ++ str ++ "\\]"
PlainMath -> do
x <- inlineListToHtml opts (readTeXMath' t str)
x <- inlineListToHtml opts (texMathToInlines t str)
let m = H.span ! A.class_ "math" $ x
let brtag = if writerHtml5 opts then H5.br else H.br
return $ case t of

View file

@ -39,7 +39,7 @@ import Text.Pandoc.Options
import Data.List ( intersperse, transpose )
import Text.Pandoc.Pretty
import Control.Monad.State
import Text.Pandoc.Readers.TeXMath (readTeXMath')
import Text.Pandoc.Readers.TeXMath (texMathToInlines)
import Network.URI (isURI)
import Data.Default
@ -319,7 +319,7 @@ inlineToHaddock opts (Math mt str) = do
let adjust x = case mt of
DisplayMath -> cr <> x <> cr
InlineMath -> x
adjust `fmap` (inlineListToHaddock opts $ readTeXMath' mt str)
adjust `fmap` (inlineListToHaddock opts $ texMathToInlines mt str)
inlineToHaddock _ (RawInline f str)
| f == "haddock" = return $ text str
| otherwise = return empty

View file

@ -331,9 +331,9 @@ inlineToMan _ (Code _ str) =
return $ text $ "\\f[C]" ++ escapeCode str ++ "\\f[]"
inlineToMan _ (Str str) = return $ text $ escapeString str
inlineToMan opts (Math InlineMath str) =
inlineListToMan opts $ readTeXMath' InlineMath str
inlineListToMan opts $ texMathToInlines InlineMath str
inlineToMan opts (Math DisplayMath str) = do
contents <- inlineListToMan opts $ readTeXMath' DisplayMath str
contents <- inlineListToMan opts $ texMathToInlines DisplayMath str
return $ cr <> text ".RS" $$ contents $$ text ".RE"
inlineToMan _ (RawInline f str)
| f == Format "man" = return $ text str

View file

@ -45,7 +45,7 @@ import Text.Pandoc.Pretty
import Control.Monad.State
import qualified Data.Set as Set
import Text.Pandoc.Writers.HTML (writeHtmlString)
import Text.Pandoc.Readers.TeXMath (readTeXMath')
import Text.Pandoc.Readers.TeXMath (texMathToInlines)
import Text.HTML.TagSoup (parseTags, isTagText, Tag(..))
import Network.URI (isURI)
import Data.Default
@ -733,7 +733,7 @@ inlineToMarkdown opts (Math InlineMath str)
return $ "\\(" <> text str <> "\\)"
| isEnabled Ext_tex_math_double_backslash opts =
return $ "\\\\(" <> text str <> "\\\\)"
| otherwise = inlineListToMarkdown opts $ readTeXMath' InlineMath str
| otherwise = inlineListToMarkdown opts $ texMathToInlines InlineMath str
inlineToMarkdown opts (Math DisplayMath str)
| isEnabled Ext_tex_math_dollars opts =
return $ "$$" <> text str <> "$$"
@ -742,7 +742,7 @@ inlineToMarkdown opts (Math DisplayMath str)
| isEnabled Ext_tex_math_double_backslash opts =
return $ "\\\\[" <> text str <> "\\\\]"
| otherwise = (\x -> cr <> x <> cr) `fmap`
inlineListToMarkdown opts (readTeXMath' DisplayMath str)
inlineListToMarkdown opts (texMathToInlines DisplayMath str)
inlineToMarkdown opts (RawInline f str)
| f == "html" || f == "markdown" ||
(isEnabled Ext_raw_tex opts && (f == "latex" || f == "tex")) =

View file

@ -380,7 +380,7 @@ inlineToOpenDocument o ils
| SmallCaps l <- ils = withTextStyle SmallC $ inlinesToOpenDocument o l
| Quoted t l <- ils = inQuotes t <$> inlinesToOpenDocument o l
| Code _ s <- ils = withTextStyle Pre $ inTextStyle $ preformatted s
| Math t s <- ils = inlinesToOpenDocument o (readTeXMath' t s)
| Math t s <- ils = inlinesToOpenDocument o (texMathToInlines t s)
| Cite _ l <- ils = inlinesToOpenDocument o l
| RawInline f s <- ils = if f == Format "opendocument"
then return $ text s

View file

@ -332,7 +332,7 @@ inlineToRTF (Quoted DoubleQuote lst) =
"\\u8220\"" ++ (inlineListToRTF lst) ++ "\\u8221\""
inlineToRTF (Code _ str) = "{\\f1 " ++ (codeStringToRTF str) ++ "}"
inlineToRTF (Str str) = stringToRTF str
inlineToRTF (Math t str) = inlineListToRTF $ readTeXMath' t str
inlineToRTF (Math t str) = inlineListToRTF $ texMathToInlines t str
inlineToRTF (Cite _ lst) = inlineListToRTF lst
inlineToRTF (RawInline f str)
| f == Format "rtf" = str