diff options
Diffstat (limited to 'Text')
-rw-r--r-- | Text/Pandoc/ASCIIMathML.hs | 14 | ||||
-rw-r--r-- | Text/Pandoc/Definition.hs | 5 | ||||
-rw-r--r-- | Text/Pandoc/LaTeXMathML.hs | 14 | ||||
-rw-r--r-- | Text/Pandoc/Readers/LaTeX.hs | 61 | ||||
-rw-r--r-- | Text/Pandoc/Readers/Markdown.hs | 11 | ||||
-rw-r--r-- | Text/Pandoc/Shared.hs | 6 | ||||
-rw-r--r-- | Text/Pandoc/Writers/ConTeXt.hs | 3 | ||||
-rw-r--r-- | Text/Pandoc/Writers/Docbook.hs | 2 | ||||
-rw-r--r-- | Text/Pandoc/Writers/HTML.hs | 24 | ||||
-rw-r--r-- | Text/Pandoc/Writers/LaTeX.hs | 3 | ||||
-rw-r--r-- | Text/Pandoc/Writers/Man.hs | 5 | ||||
-rw-r--r-- | Text/Pandoc/Writers/Markdown.hs | 3 | ||||
-rw-r--r-- | Text/Pandoc/Writers/MediaWiki.hs | 2 | ||||
-rw-r--r-- | Text/Pandoc/Writers/OpenDocument.hs | 2 | ||||
-rw-r--r-- | Text/Pandoc/Writers/RST.hs | 6 | ||||
-rw-r--r-- | Text/Pandoc/Writers/RTF.hs | 2 | ||||
-rw-r--r-- | Text/Pandoc/Writers/Texinfo.hs | 5 |
17 files changed, 91 insertions, 77 deletions
diff --git a/Text/Pandoc/ASCIIMathML.hs b/Text/Pandoc/ASCIIMathML.hs deleted file mode 100644 index 233040dcc..000000000 --- a/Text/Pandoc/ASCIIMathML.hs +++ /dev/null @@ -1,14 +0,0 @@ -{-# LANGUAGE CPP, TemplateHaskell #-} --- | Definitions for use of ASCIIMathML in HTML. --- (See <http://www1.chapman.edu/~jipsen/mathml/asciimath.html>.) -module Text.Pandoc.ASCIIMathML ( asciiMathMLScript ) where -import Text.Pandoc.TH ( contentsOf ) -import System.FilePath ( (</>) ) - --- | String containing ASCIIMathML javascript. -asciiMathMLScript :: String -#ifndef __HADDOCK__ -asciiMathMLScript = "<script type=\"text/javascript\">\n" ++ - $(contentsOf $ "data" </> "ASCIIMathML.js.comment") ++ - $(contentsOf $ "data" </> "ASCIIMathML.js.packed") ++ "</script>\n" -#endif diff --git a/Text/Pandoc/Definition.hs b/Text/Pandoc/Definition.hs index e97a2a53a..66c3ab878 100644 --- a/Text/Pandoc/Definition.hs +++ b/Text/Pandoc/Definition.hs @@ -98,6 +98,9 @@ data QuoteType = SingleQuote | DoubleQuote deriving (Show, Eq, Read, Typeable, D -- | Link target (URL, title). type Target = (String, String) +-- | Type of math element (display or inline). +data MathType = DisplayMath | InlineMath deriving (Show, Eq, Read, Typeable, Data) + -- | Inline elements. data Inline = Str String -- ^ Text (string) @@ -116,7 +119,7 @@ data Inline | Apostrophe -- ^ Apostrophe | Ellipses -- ^ Ellipses | LineBreak -- ^ Hard line break - | Math String -- ^ TeX math (literal) + | Math MathType String -- ^ TeX math (literal) | TeX String -- ^ LaTeX code (literal) | HtmlInline String -- ^ HTML code (literal) | Link [Inline] Target -- ^ Hyperlink: text (list of inlines), target diff --git a/Text/Pandoc/LaTeXMathML.hs b/Text/Pandoc/LaTeXMathML.hs new file mode 100644 index 000000000..de0d3875f --- /dev/null +++ b/Text/Pandoc/LaTeXMathML.hs @@ -0,0 +1,14 @@ +{-# LANGUAGE CPP, TemplateHaskell #-} +-- | Definitions for use of LaTeXMathML in HTML. +-- (See http://math.etsu.edu/LaTeXMathML/) +module Text.Pandoc.LaTeXMathML ( latexMathMLScript ) where +import Text.Pandoc.TH ( contentsOf ) +import System.FilePath ( (</>) ) + +-- | String containing LaTeXMathML javascript. +latexMathMLScript :: String +#ifndef __HADDOCK__ +latexMathMLScript = "<script type=\"text/javascript\">\n" ++ + $(contentsOf $ "data" </> "LaTeXMathML.js.comment") ++ + $(contentsOf $ "data" </> "LaTeXMathML.js.packed") ++ "</script>\n" +#endif diff --git a/Text/Pandoc/Readers/LaTeX.hs b/Text/Pandoc/Readers/LaTeX.hs index 2ce0204ee..883c1bbd1 100644 --- a/Text/Pandoc/Readers/LaTeX.hs +++ b/Text/Pandoc/Readers/LaTeX.hs @@ -153,7 +153,6 @@ block = choice [ hrule , header , list , blockQuote - , mathBlock , comment , bibliographic , para @@ -219,26 +218,6 @@ blockQuote = (environment "quote" <|> environment "quotation") >>~ spaces >>= return . BlockQuote -- --- math block --- - -mathBlock :: GenParser Char st Block -mathBlock = mathBlockWith (begin "equation") (end "equation") <|> - mathBlockWith (begin "displaymath") (end "displaymath") <|> - mathBlockWith (try $ string "\\[") (try $ string "\\]") <?> - "math block" - -mathBlockWith :: GenParser Char st t - -> GenParser Char st end - -> GenParser Char st Block -mathBlockWith start end' = try $ do - start - spaces - result <- manyTill anyChar end' - spaces - return $ BlockQuote [Para [Math result]] - --- -- list blocks -- @@ -683,21 +662,31 @@ endline = try $ newline >> notFollowedBy blankline >> return Space -- math math :: GenParser Char st Inline -math = math1 <|> math2 <?> "math" - -math1 :: GenParser Char st Inline -math1 = try $ do - char '$' - result <- many (noneOf "$") - char '$' - return $ Math result - -math2 :: GenParser Char st Inline -math2 = try $ do - string "\\(" - result <- many (noneOf "$") - string "\\)" - return $ Math result +math = (math3 >>= return . Math DisplayMath) + <|> (math1 >>= return . Math InlineMath) + <|> (math2 >>= return . Math InlineMath) + <|> (math4 >>= return . Math DisplayMath) + <|> (math5 >>= return . Math DisplayMath) + <|> (math6 >>= return . Math DisplayMath) + <?> "math" + +math1 :: GenParser Char st String +math1 = try $ char '$' >> manyTill anyChar (char '$') + +math2 :: GenParser Char st String +math2 = try $ string "\\(" >> manyTill anyChar (try $ string "\\)") + +math3 :: GenParser Char st String +math3 = try $ char '$' >> math1 >>~ char '$' + +math4 :: GenParser Char st String +math4 = try $ (begin "equation") >> spaces >> manyTill anyChar (end "equation") + +math5 :: GenParser Char st String +math5 = try $ (begin "displaymath") >> spaces >> manyTill anyChar (end "displaymath") + +math6 :: GenParser Char st String +math6 = try $ (string "\\[") >> spaces >> manyTill anyChar (try $ string "\\]") -- -- links and images diff --git a/Text/Pandoc/Readers/Markdown.hs b/Text/Pandoc/Readers/Markdown.hs index ac7096d37..f030f07ad 100644 --- a/Text/Pandoc/Readers/Markdown.hs +++ b/Text/Pandoc/Readers/Markdown.hs @@ -870,14 +870,21 @@ mathWord = many1 ((noneOf " \t\n\\$") <|> (try (char '\\') >>~ notFollowedBy (char '$'))) math :: GenParser Char ParserState Inline -math = try $ do +math = (mathDisplay >>= return . Math DisplayMath) + <|> (mathInline >>= return . Math InlineMath) + +mathDisplay :: GenParser Char ParserState String +mathDisplay = try $ char '$' >> mathInline >>~ char '$' >>~ notFollowedBy digit + +mathInline :: GenParser Char ParserState String +mathInline = try $ do failIfStrict char '$' notFollowedBy space words' <- sepBy1 mathWord (many1 (spaceChar <|> (newline >>~ notFollowedBy' blankline))) char '$' notFollowedBy digit - return $ Math $ joinWithSep " " words' + return $ joinWithSep " " words' emph :: GenParser Char ParserState Inline emph = ((enclosed (char '*') (notFollowedBy' strong >> char '*') inline) <|> diff --git a/Text/Pandoc/Shared.hs b/Text/Pandoc/Shared.hs index d14a49d82..38c1cf6b4 100644 --- a/Text/Pandoc/Shared.hs +++ b/Text/Pandoc/Shared.hs @@ -715,8 +715,8 @@ refsMatch ((Quoted t x):restx) ((Quoted u y):resty) = t == u && refsMatch x y && refsMatch restx resty refsMatch ((Code x):restx) ((Code y):resty) = ((map toLower x) == (map toLower y)) && refsMatch restx resty -refsMatch ((Math x):restx) ((Math y):resty) = - ((map toLower x) == (map toLower y)) && refsMatch restx resty +refsMatch ((Math t x):restx) ((Math u y):resty) = + ((map toLower x) == (map toLower y)) && t == u && refsMatch restx resty refsMatch ((TeX x):restx) ((TeX y):resty) = ((map toLower x) == (map toLower y)) && refsMatch restx resty refsMatch ((HtmlInline x):restx) ((HtmlInline y):resty) = @@ -876,7 +876,7 @@ isHeaderBlock _ = False -- data HTMLMathMethod = PlainMath - | ASCIIMathML (Maybe String) -- url of ASCIIMathML.js + | LaTeXMathML (Maybe String) -- url of LaTeXMathML.js | GladTeX | MimeTeX String -- url of mimetex.cgi deriving (Show, Read, Eq) diff --git a/Text/Pandoc/Writers/ConTeXt.hs b/Text/Pandoc/Writers/ConTeXt.hs index 62e205ee5..7f5af4191 100644 --- a/Text/Pandoc/Writers/ConTeXt.hs +++ b/Text/Pandoc/Writers/ConTeXt.hs @@ -272,7 +272,8 @@ inlineToConTeXt EmDash = return $ text "---" inlineToConTeXt EnDash = return $ text "--" inlineToConTeXt Ellipses = return $ text "\\ldots{}" inlineToConTeXt (Str str) = return $ text $ stringToConTeXt str -inlineToConTeXt (Math str) = return $ char '$' <> text str <> char '$' +inlineToConTeXt (Math InlineMath str) = return $ char '$' <> text str <> char '$' +inlineToConTeXt (Math DisplayMath str) = return $ text "\\startformula " <> text str <> text " \\stopformula" inlineToConTeXt (TeX str) = return $ text str inlineToConTeXt (HtmlInline _) = return empty inlineToConTeXt (LineBreak) = return $ text "\\crlf\n" diff --git a/Text/Pandoc/Writers/Docbook.hs b/Text/Pandoc/Writers/Docbook.hs index 5b433c434..9ed4e808f 100644 --- a/Text/Pandoc/Writers/Docbook.hs +++ b/Text/Pandoc/Writers/Docbook.hs @@ -236,7 +236,7 @@ inlineToDocbook _ EmDash = text "—" inlineToDocbook _ EnDash = text "–" inlineToDocbook _ (Code str) = inTagsSimple "literal" $ text (escapeStringForXML str) -inlineToDocbook opts (Math str) = inlinesToDocbook opts $ readTeXMath str +inlineToDocbook opts (Math _ str) = inlinesToDocbook opts $ readTeXMath str inlineToDocbook _ (TeX _) = empty inlineToDocbook _ (HtmlInline _) = empty inlineToDocbook _ LineBreak = text $ "<literallayout></literallayout>" diff --git a/Text/Pandoc/Writers/HTML.hs b/Text/Pandoc/Writers/HTML.hs index e5ed4468e..4af644a91 100644 --- a/Text/Pandoc/Writers/HTML.hs +++ b/Text/Pandoc/Writers/HTML.hs @@ -30,7 +30,7 @@ Conversion of 'Pandoc' documents to HTML. -} module Text.Pandoc.Writers.HTML ( writeHtml , writeHtmlString ) where import Text.Pandoc.Definition -import Text.Pandoc.ASCIIMathML +import Text.Pandoc.LaTeXMathML import Text.Pandoc.CharacterReferences ( decodeCharacterReferences ) import Text.Pandoc.Shared import Text.Pandoc.Readers.TeXMath @@ -123,9 +123,9 @@ writeHtml opts (Pandoc (Meta tit authors date) blocks) = '\n':(unlines $ S.toList cssLines) math = if stMath newstate then case writerHTMLMathMethod opts of - ASCIIMathML Nothing -> - primHtml asciiMathMLScript - ASCIIMathML (Just url) -> + LaTeXMathML Nothing -> + primHtml latexMathMLScript + LaTeXMathML (Just url) -> script ! [src url, thetype "text/javascript"] $ noHtml @@ -268,7 +268,7 @@ inlineListToIdentifier' (x:xs) = Apostrophe -> "" Ellipses -> "" LineBreak -> "-" - Math _ -> "" + Math _ _ -> "" TeX _ -> "" HtmlInline _ -> "" Link lst _ -> inlineListToIdentifier' lst @@ -455,10 +455,13 @@ inlineToHtml opts inline = primHtmlChar "rdquo") in do contents <- inlineListToHtml opts lst return $ leftQuote +++ contents +++ rightQuote - (Math str) -> modify (\st -> st {stMath = True}) >> + (Math t str) -> + modify (\st -> st {stMath = True}) >> (case writerHTMLMathMethod opts of - ASCIIMathML _ -> - return $ stringToHtml ("$" ++ str ++ "$") + LaTeXMathML _ -> + return $ if t == InlineMath + then primHtml ("$" ++ str ++ "$") + else primHtml ("$$" ++ str ++ "$$") MimeTeX url -> return $ image ! [src (url ++ "?" ++ str), alt str, title str] @@ -467,7 +470,10 @@ inlineToHtml opts inline = PlainMath -> inlineListToHtml opts (readTeXMath str) >>= return . (thespan ! [theclass "math"])) - (TeX _) -> return noHtml + (TeX str) -> case writerHTMLMathMethod opts of + LaTeXMathML _ -> do modify (\st -> st {stMath = True}) + return $ primHtml str + _ -> return noHtml (HtmlInline str) -> return $ primHtml str (Link [Code str] (s,_)) | "mailto:" `isPrefixOf` s -> return $ obfuscateLink opts str s diff --git a/Text/Pandoc/Writers/LaTeX.hs b/Text/Pandoc/Writers/LaTeX.hs index 89170dee1..a13c51b30 100644 --- a/Text/Pandoc/Writers/LaTeX.hs +++ b/Text/Pandoc/Writers/LaTeX.hs @@ -299,7 +299,8 @@ inlineToLaTeX EmDash = return $ text "---" inlineToLaTeX EnDash = return $ text "--" inlineToLaTeX Ellipses = return $ text "\\ldots{}" inlineToLaTeX (Str str) = return $ text $ stringToLaTeX str -inlineToLaTeX (Math str) = return $ char '$' <> text str <> char '$' +inlineToLaTeX (Math InlineMath str) = return $ char '$' <> text str <> char '$' +inlineToLaTeX (Math DisplayMath str) = return $ text "\\[" <> text str <> text "\\]" inlineToLaTeX (TeX str) = return $ text str inlineToLaTeX (HtmlInline _) = return empty inlineToLaTeX (LineBreak) = return $ text "\\\\" diff --git a/Text/Pandoc/Writers/Man.hs b/Text/Pandoc/Writers/Man.hs index 9037c24af..0bd6b92ef 100644 --- a/Text/Pandoc/Writers/Man.hs +++ b/Text/Pandoc/Writers/Man.hs @@ -272,7 +272,10 @@ inlineToMan _ Ellipses = return $ text "\\&..." inlineToMan _ (Code str) = return $ text $ "\\f[B]" ++ escapeCode str ++ "\\f[]" inlineToMan _ (Str str) = return $ text $ escapeString str -inlineToMan opts (Math str) = inlineToMan opts (Code str) +inlineToMan opts (Math InlineMath str) = inlineToMan opts (Code str) +inlineToMan opts (Math DisplayMath str) = do + contents <- inlineToMan opts (Code str) + return $ text ".RS" $$ contents $$ text ".RE" inlineToMan _ (TeX _) = return empty inlineToMan _ (HtmlInline str) = return $ text $ escapeCode str inlineToMan _ (LineBreak) = return $ text "\n.PD 0\n.P\n.PD\n" diff --git a/Text/Pandoc/Writers/Markdown.hs b/Text/Pandoc/Writers/Markdown.hs index 7c360bec2..d8ad8454f 100644 --- a/Text/Pandoc/Writers/Markdown.hs +++ b/Text/Pandoc/Writers/Markdown.hs @@ -337,7 +337,8 @@ inlineToMarkdown _ (Code str) = spacer = if (longest == 0) then "" else " " in return $ text (marker ++ spacer ++ str ++ spacer ++ marker) inlineToMarkdown _ (Str str) = return $ text $ escapeString str -inlineToMarkdown _ (Math str) = return $ char '$' <> text str <> char '$' +inlineToMarkdown _ (Math InlineMath str) = return $ char '$' <> text str <> char '$' +inlineToMarkdown _ (Math DisplayMath str) = return $ text "$$" <> text str <> text "$$" inlineToMarkdown _ (TeX str) = return $ text str inlineToMarkdown _ (HtmlInline str) = return $ text str inlineToMarkdown _ (LineBreak) = return $ text " \n" diff --git a/Text/Pandoc/Writers/MediaWiki.hs b/Text/Pandoc/Writers/MediaWiki.hs index 97d9d00c6..7d43c6fc4 100644 --- a/Text/Pandoc/Writers/MediaWiki.hs +++ b/Text/Pandoc/Writers/MediaWiki.hs @@ -357,7 +357,7 @@ inlineToMediaWiki _ (Code str) = inlineToMediaWiki _ (Str str) = return $ escapeString str -inlineToMediaWiki _ (Math str) = return $ "<math>" ++ str ++ "</math>" +inlineToMediaWiki _ (Math _ str) = return $ "<math>" ++ str ++ "</math>" -- note: str should NOT be escaped inlineToMediaWiki _ (TeX _) = return "" diff --git a/Text/Pandoc/Writers/OpenDocument.hs b/Text/Pandoc/Writers/OpenDocument.hs index 70aab92f1..875ab5fa8 100644 --- a/Text/Pandoc/Writers/OpenDocument.hs +++ b/Text/Pandoc/Writers/OpenDocument.hs @@ -379,7 +379,7 @@ inlineToOpenDocument o ils | SmallCaps l <- ils = withTextStyle SmallC $ inlinesToOpenDocument o l | Quoted t l <- ils = inQuotes t <$> inlinesToOpenDocument o l | Code s <- ils = preformatted s - | Math s <- ils = inlinesToOpenDocument o (readTeXMath s) + | Math _ s <- ils = inlinesToOpenDocument o (readTeXMath s) | Cite _ l <- ils = inlinesToOpenDocument o l | TeX s <- ils = preformatted s | HtmlInline s <- ils = preformatted s diff --git a/Text/Pandoc/Writers/RST.hs b/Text/Pandoc/Writers/RST.hs index 9215f051d..de65bcf0e 100644 --- a/Text/Pandoc/Writers/RST.hs +++ b/Text/Pandoc/Writers/RST.hs @@ -291,14 +291,16 @@ inlineToRST Apostrophe = return $ char '\'' inlineToRST Ellipses = return $ text "..." inlineToRST (Code str) = return $ text $ "``" ++ str ++ "``" inlineToRST (Str str) = return $ text $ escapeString str -inlineToRST (Math str) = do +inlineToRST (Math t str) = do includes <- get >>= (return . stIncludes) let rawMathRole = ".. role:: math(raw)\n" ++ " :format: html latex\n" if not (rawMathRole `elem` includes) then modify $ \st -> st { stIncludes = rawMathRole : includes } else return () - return $ text $ ":math:`$" ++ str ++ "$`" + return $ if t == InlineMath + then text $ ":math:`$" ++ str ++ "$`" + else text $ ":math:`$$" ++ str ++ "$$`" inlineToRST (TeX _) = return empty inlineToRST (HtmlInline _) = return empty inlineToRST (LineBreak) = do diff --git a/Text/Pandoc/Writers/RTF.hs b/Text/Pandoc/Writers/RTF.hs index d0fbfb53a..e31a162a5 100644 --- a/Text/Pandoc/Writers/RTF.hs +++ b/Text/Pandoc/Writers/RTF.hs @@ -275,7 +275,7 @@ inlineToRTF EmDash = "\\u8212-" inlineToRTF EnDash = "\\u8211-" inlineToRTF (Code str) = "{\\f1 " ++ (codeStringToRTF str) ++ "}" inlineToRTF (Str str) = stringToRTF str -inlineToRTF (Math str) = inlineListToRTF $ readTeXMath str +inlineToRTF (Math _ str) = inlineListToRTF $ readTeXMath str inlineToRTF (Cite _ lst) = inlineListToRTF lst inlineToRTF (TeX _) = "" inlineToRTF (HtmlInline _) = "" diff --git a/Text/Pandoc/Writers/Texinfo.hs b/Text/Pandoc/Writers/Texinfo.hs index d0e134346..305a1a8d0 100644 --- a/Text/Pandoc/Writers/Texinfo.hs +++ b/Text/Pandoc/Writers/Texinfo.hs @@ -30,6 +30,7 @@ Conversion of 'Pandoc' format into Texinfo. module Text.Pandoc.Writers.Texinfo ( writeTexinfo ) where import Text.Pandoc.Definition import Text.Pandoc.Shared +import Text.Pandoc.Readers.TeXMath import Text.Printf ( printf ) import Data.List ( isSuffixOf ) import Data.Char ( chr, ord ) @@ -364,7 +365,7 @@ inlineForNode EnDash = return $ text "--" inlineForNode Apostrophe = return $ char '\'' inlineForNode Ellipses = return $ text "..." inlineForNode LineBreak = return empty -inlineForNode (Math _) = return empty +inlineForNode (Math _ str) = inlineListForNode $ readTeXMath str inlineForNode (TeX _) = return empty inlineForNode (HtmlInline _) = return empty inlineForNode (Link lst _) = inlineListForNode lst @@ -437,7 +438,7 @@ inlineToTexinfo EmDash = return $ text "---" inlineToTexinfo EnDash = return $ text "--" inlineToTexinfo Ellipses = return $ text "@dots{}" inlineToTexinfo (Str str) = return $ text (stringToTexinfo str) -inlineToTexinfo (Math str) = return $ inCmd "math" $ text str +inlineToTexinfo (Math _ str) = return $ inCmd "math" $ text str inlineToTexinfo (TeX str) = return $ text "@tex" $$ text str $$ text "@end tex" inlineToTexinfo (HtmlInline _) = return empty inlineToTexinfo (LineBreak) = return $ text "@*" |