diff options
author | John MacFarlane <jgm@berkeley.edu> | 2014-08-04 11:13:09 -0700 |
---|---|---|
committer | John MacFarlane <jgm@berkeley.edu> | 2014-08-04 11:13:09 -0700 |
commit | 40d8100d440dd7924068d027e052f5a3de65e70f (patch) | |
tree | 6383616e5095559dbe9d02e9960a965dc69c5c53 /src/Text | |
parent | 4630cff2a6c116f1d474f459e6e759f5ce7f2003 (diff) | |
download | pandoc-40d8100d440dd7924068d027e052f5a3de65e70f.tar.gz |
Use texmath 0.7 interface.
Diffstat (limited to 'src/Text')
-rw-r--r-- | src/Text/Pandoc/Parsing.hs | 3 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/HTML.hs | 4 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/Org.hs | 7 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/TeXMath.hs | 7 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/Docbook.hs | 15 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/Docx.hs | 4 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/HTML.hs | 13 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/ODT.hs | 3 |
8 files changed, 32 insertions, 24 deletions
diff --git a/src/Text/Pandoc/Parsing.hs b/src/Text/Pandoc/Parsing.hs index b25fca100..d1fba1e21 100644 --- a/src/Text/Pandoc/Parsing.hs +++ b/src/Text/Pandoc/Parsing.hs @@ -178,7 +178,8 @@ import Data.Char ( toLower, toUpper, ord, chr, isAscii, isAlphaNum, import Data.List ( intercalate, transpose ) import Text.Pandoc.Shared import qualified Data.Map as M -import Text.TeXMath.Macros (applyMacros, Macro, parseMacroDefinitions) +import Text.TeXMath.Readers.TeX.Macros (applyMacros, Macro, + parseMacroDefinitions) import Text.Pandoc.Compat.TagSoupEntity ( lookupEntity ) import Text.Pandoc.Asciify (toAsciiChar) import Data.Default diff --git a/src/Text/Pandoc/Readers/HTML.hs b/src/Text/Pandoc/Readers/HTML.hs index 2e8b56124..1ded83ff1 100644 --- a/src/Text/Pandoc/Readers/HTML.hs +++ b/src/Text/Pandoc/Readers/HTML.hs @@ -57,7 +57,7 @@ import Control.Applicative ( (<$>), (<$), (<*), (*>), (<|>)) import Data.Monoid (mconcat, Monoid, mempty, (<>), First (..)) import Text.Printf (printf) import Debug.Trace (trace) -import Text.TeXMath (readMathML, writeTeXMath) +import Text.TeXMath (readMathML, writeTeX) import Data.Default (Default (..), def) import Control.Monad.Reader (Reader,ask, asks, local, runReader) @@ -572,7 +572,7 @@ pRawHtmlInline = do else return mempty mathMLToTeXMath :: String -> Either String String -mathMLToTeXMath s = writeTeXMath <$> readMathML s +mathMLToTeXMath s = writeTeX <$> readMathML s pMath :: Bool -> TagParser Inlines pMath inCase = try $ do diff --git a/src/Text/Pandoc/Readers/Org.hs b/src/Text/Pandoc/Readers/Org.hs index 34e98380e..065f5a046 100644 --- a/src/Text/Pandoc/Readers/Org.hs +++ b/src/Text/Pandoc/Readers/Org.hs @@ -41,7 +41,7 @@ import Text.Pandoc.Parsing hiding ( F, unF, askF, asksF, runF ) import Text.Pandoc.Readers.LaTeX (inlineCommand, rawLaTeXInline) import Text.Pandoc.Shared (compactify', compactify'DL) -import Text.TeXMath (texMathToPandoc, DisplayType(..)) +import Text.TeXMath (readTeX, writePandoc, DisplayType(..)) import Control.Applicative ( Applicative, pure , (<$>), (<$), (<*>), (<*), (*>) ) @@ -1383,7 +1383,7 @@ inlineLaTeX = try $ do maybe mzero returnF $ parseAsMath cmd `mplus` parseAsInlineLaTeX cmd where parseAsMath :: String -> Maybe Inlines - parseAsMath cs = maybeRight $ B.fromList <$> texMathToPandoc DisplayInline cs + parseAsMath cs = B.fromList <$> texMathToPandoc cs parseAsInlineLaTeX :: String -> Maybe Inlines parseAsInlineLaTeX cs = maybeRight $ runParser inlineCommand state "" cs @@ -1391,6 +1391,9 @@ inlineLaTeX = try $ do state :: ParserState state = def{ stateOptions = def{ readerParseRaw = True }} + texMathToPandoc inp = (maybeRight $ readTeX inp) >>= + writePandoc DisplayInline + maybeRight :: Either a b -> Maybe b maybeRight = either (const Nothing) Just diff --git a/src/Text/Pandoc/Readers/TeXMath.hs b/src/Text/Pandoc/Readers/TeXMath.hs index d7f982fb7..3fee3051e 100644 --- a/src/Text/Pandoc/Readers/TeXMath.hs +++ b/src/Text/Pandoc/Readers/TeXMath.hs @@ -38,9 +38,10 @@ import Text.TeXMath texMathToInlines :: MathType -> String -- ^ String to parse (assumes @'\n'@ line endings) -> [Inline] -texMathToInlines mt inp = case texMathToPandoc dt inp of - Left _ -> [Str (delim ++ inp ++ delim)] - Right res -> res +texMathToInlines mt inp = + case writePandoc dt `fmap` readTeX inp of + Right (Just ils) -> ils + _ -> [Str (delim ++ inp ++ delim)] where (dt, delim) = case mt of DisplayMath -> (DisplayBlock, "$$") InlineMath -> (DisplayInline, "$") diff --git a/src/Text/Pandoc/Writers/Docbook.hs b/src/Text/Pandoc/Writers/Docbook.hs index 25c1e156e..67df45348 100644 --- a/src/Text/Pandoc/Writers/Docbook.hs +++ b/src/Text/Pandoc/Writers/Docbook.hs @@ -39,6 +39,7 @@ import Text.Pandoc.Templates (renderTemplate') import Text.Pandoc.Readers.TeXMath import Data.List ( isPrefixOf, intercalate, isSuffixOf ) import Data.Char ( toLower ) +import Control.Applicative ((<$>)) import Data.Monoid ( Any(..) ) import Text.Pandoc.Highlighting ( languages, languagesByExtension ) import Text.Pandoc.Pretty @@ -293,13 +294,13 @@ inlineToDocbook _ (Code _ str) = inTagsSimple "literal" $ text (escapeStringForXML str) inlineToDocbook opts (Math t str) | isMathML (writerHTMLMathMethod opts) = - case texMathToMathML dt str of - Right r -> inTagsSimple tagtype - $ text $ Xml.ppcElement conf - $ fixNS - $ removeAttr r - Left _ -> inlinesToDocbook opts - $ texMathToInlines t str + case writeMathML dt <$> readTeX str of + Right r -> inTagsSimple tagtype + $ text $ Xml.ppcElement conf + $ fixNS + $ removeAttr r + Left _ -> inlinesToDocbook opts + $ texMathToInlines t str | otherwise = inlinesToDocbook opts $ texMathToInlines t str where (dt, tagtype) = case t of InlineMath -> (DisplayInline,"inlineequation") diff --git a/src/Text/Pandoc/Writers/Docx.hs b/src/Text/Pandoc/Writers/Docx.hs index 6be6eb1d3..5e02419d8 100644 --- a/src/Text/Pandoc/Writers/Docx.hs +++ b/src/Text/Pandoc/Writers/Docx.hs @@ -58,7 +58,7 @@ import System.Random (randomRIO) import Text.Printf (printf) import qualified Control.Exception as E import Text.Pandoc.MIME (getMimeType, extensionFromMimeType) -import Control.Applicative ((<|>)) +import Control.Applicative ((<|>), (<$>)) import Data.Maybe (mapMaybe) data ListMarker = NoMarker @@ -767,7 +767,7 @@ inlineToOpenXML opts (Math mathType str) = do let displayType = if mathType == DisplayMath then DisplayBlock else DisplayInline - case texMathToOMML displayType str of + case writeOMML displayType <$> readTeX str of Right r -> return [r] Left _ -> inlinesToOpenXML opts (texMathToInlines mathType str) inlineToOpenXML opts (Cite _ lst) = inlinesToOpenXML opts lst diff --git a/src/Text/Pandoc/Writers/HTML.hs b/src/Text/Pandoc/Writers/HTML.hs index 4cd21ff4c..a34f6b4dd 100644 --- a/src/Text/Pandoc/Writers/HTML.hs +++ b/src/Text/Pandoc/Writers/HTML.hs @@ -63,6 +63,7 @@ import Text.XML.Light.Output import System.FilePath (takeExtension) import Data.Monoid import Data.Aeson (Value) +import Control.Applicative ((<$>)) data WriterState = WriterState { stNotes :: [Html] -- ^ List of notes @@ -700,12 +701,12 @@ inlineToHtml opts inline = else DisplayBlock let conf = useShortEmptyTags (const False) defaultConfigPP - case texMathToMathML dt str of - Right r -> return $ preEscapedString $ - ppcElement conf r - Left _ -> inlineListToHtml opts - (texMathToInlines t str) >>= return . - (H.span ! A.class_ "math") + case writeMathML dt <$> readTeX str of + Right r -> return $ preEscapedString $ + ppcElement conf r + Left _ -> inlineListToHtml opts + (texMathToInlines t str) >>= + return . (H.span ! A.class_ "math") MathJax _ -> return $ H.span ! A.class_ "math" $ toHtml $ case t of InlineMath -> "\\(" ++ str ++ "\\)" diff --git a/src/Text/Pandoc/Writers/ODT.hs b/src/Text/Pandoc/Writers/ODT.hs index 02794f76d..feaa0167c 100644 --- a/src/Text/Pandoc/Writers/ODT.hs +++ b/src/Text/Pandoc/Writers/ODT.hs @@ -37,6 +37,7 @@ import Text.TeXMath import qualified Data.ByteString.Lazy as B import Text.Pandoc.UTF8 ( fromStringLazy ) import Codec.Archive.Zip +import Control.Applicative ((<$>)) import Text.Pandoc.Options ( WriterOptions(..) ) import Text.Pandoc.Shared ( stringify, readDataFile, fetchItem', warn ) import Text.Pandoc.ImageSize ( imageSize, sizeInPoints ) @@ -150,7 +151,7 @@ transformPicMath opts entriesRef (Image lab (src,_)) = do transformPicMath _ entriesRef (Math t math) = do entries <- readIORef entriesRef let dt = if t == InlineMath then DisplayInline else DisplayBlock - case texMathToMathML dt math of + case writeMathML dt <$> readTeX math of Left _ -> return $ Math t math Right r -> do let conf = useShortEmptyTags (const False) defaultConfigPP |