diff options
author | John MacFarlane <jgm@berkeley.edu> | 2014-07-19 17:18:35 -0700 |
---|---|---|
committer | John MacFarlane <jgm@berkeley.edu> | 2014-07-19 17:18:35 -0700 |
commit | a7b64532f54725ebc20f066295307389b8b4cbe0 (patch) | |
tree | 83ace6cd007e1e891b3010f6b836350c0d90eadc /src/Text/Pandoc/Writers | |
parent | 999b952a212af0e33183068ff4a55edc5aafde62 (diff) | |
parent | e7d8039969fd177da91b871f3bc4b73950cc7bc8 (diff) | |
download | pandoc-a7b64532f54725ebc20f066295307389b8b4cbe0.tar.gz |
Merge pull request #1438 from mpickering/master
Renamed readTeXMath' to avoid name conflict with texmath 0.6.7
Diffstat (limited to 'src/Text/Pandoc/Writers')
-rw-r--r-- | src/Text/Pandoc/Writers/Docbook.hs | 4 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/Docx.hs | 2 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/HTML.hs | 4 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/Haddock.hs | 4 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/Man.hs | 4 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/Markdown.hs | 6 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/OpenDocument.hs | 2 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/RTF.hs | 2 |
8 files changed, 14 insertions, 14 deletions
diff --git a/src/Text/Pandoc/Writers/Docbook.hs b/src/Text/Pandoc/Writers/Docbook.hs index ba6a92a08..25c1e156e 100644 --- a/src/Text/Pandoc/Writers/Docbook.hs +++ b/src/Text/Pandoc/Writers/Docbook.hs @@ -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") diff --git a/src/Text/Pandoc/Writers/Docx.hs b/src/Text/Pandoc/Writers/Docx.hs index 4b787b023..de31e462e 100644 --- a/src/Text/Pandoc/Writers/Docx.hs +++ b/src/Text/Pandoc/Writers/Docx.hs @@ -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") diff --git a/src/Text/Pandoc/Writers/HTML.hs b/src/Text/Pandoc/Writers/HTML.hs index 3f4c19b67..4cd21ff4c 100644 --- a/src/Text/Pandoc/Writers/HTML.hs +++ b/src/Text/Pandoc/Writers/HTML.hs @@ -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 diff --git a/src/Text/Pandoc/Writers/Haddock.hs b/src/Text/Pandoc/Writers/Haddock.hs index 1c82839d0..14f398da9 100644 --- a/src/Text/Pandoc/Writers/Haddock.hs +++ b/src/Text/Pandoc/Writers/Haddock.hs @@ -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 diff --git a/src/Text/Pandoc/Writers/Man.hs b/src/Text/Pandoc/Writers/Man.hs index 41eb3e5be..2af7c0e31 100644 --- a/src/Text/Pandoc/Writers/Man.hs +++ b/src/Text/Pandoc/Writers/Man.hs @@ -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 diff --git a/src/Text/Pandoc/Writers/Markdown.hs b/src/Text/Pandoc/Writers/Markdown.hs index 2028bf593..f581a1058 100644 --- a/src/Text/Pandoc/Writers/Markdown.hs +++ b/src/Text/Pandoc/Writers/Markdown.hs @@ -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")) = diff --git a/src/Text/Pandoc/Writers/OpenDocument.hs b/src/Text/Pandoc/Writers/OpenDocument.hs index e2b9a68f1..773d142f4 100644 --- a/src/Text/Pandoc/Writers/OpenDocument.hs +++ b/src/Text/Pandoc/Writers/OpenDocument.hs @@ -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 diff --git a/src/Text/Pandoc/Writers/RTF.hs b/src/Text/Pandoc/Writers/RTF.hs index 5c8c49f3e..fe241b8d7 100644 --- a/src/Text/Pandoc/Writers/RTF.hs +++ b/src/Text/Pandoc/Writers/RTF.hs @@ -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 |