aboutsummaryrefslogtreecommitdiff
path: root/Text
diff options
context:
space:
mode:
Diffstat (limited to 'Text')
-rw-r--r--Text/Pandoc/Readers/TeXMath.hs218
-rw-r--r--Text/Pandoc/Writers/Docbook.hs3
-rw-r--r--Text/Pandoc/Writers/HTML.hs19
-rw-r--r--Text/Pandoc/Writers/Man.hs5
-rw-r--r--Text/Pandoc/Writers/RST.hs7
-rw-r--r--Text/Pandoc/Writers/RTF.hs3
6 files changed, 237 insertions, 18 deletions
diff --git a/Text/Pandoc/Readers/TeXMath.hs b/Text/Pandoc/Readers/TeXMath.hs
new file mode 100644
index 000000000..918bb0670
--- /dev/null
+++ b/Text/Pandoc/Readers/TeXMath.hs
@@ -0,0 +1,218 @@
+{-
+Copyright (C) 2007 John MacFarlane <jgm@berkeley.edu>
+
+This program is free software; you can redistribute it and/or modify
+it under the terms of the GNU General Public License as published by
+the Free Software Foundation; either version 2 of the License, or
+(at your option) any later version.
+
+This program is distributed in the hope that it will be useful,
+but WITHOUT ANY WARRANTY; without even the implied warranty of
+MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
+GNU General Public License for more details.
+
+You should have received a copy of the GNU General Public License
+along with this program; if not, write to the Free Software
+Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
+-}
+
+{- |
+ Module : Text.Pandoc.Readers.TeXMath
+ Copyright : Copyright (C) 2007 John MacFarlane
+ License : GNU GPL, version 2 or above
+
+ Maintainer : John MacFarlane <jgm@berkeley.edu>
+ Stability : alpha
+ Portability : portable
+
+Conversion of TeX math to a list of 'Pandoc' inline elements.
+-}
+module Text.Pandoc.Readers.TeXMath (
+ readTeXMath
+ ) where
+
+import Text.ParserCombinators.Parsec
+import Text.Pandoc.UTF8
+import Text.Pandoc.Definition
+import Text.Pandoc.Shared
+
+-- | Converts a string of raw TeX math to a list of 'Pandoc' inlines.
+readTeXMath :: String -> [Inline]
+readTeXMath inp = case parse teXMath "input" inp of
+ Left err -> error $ "\nError:\n" ++ show err
+ Right res -> res
+
+teXMath = manyTill mathPart eof >>= return . concat
+
+mathPart = whitespace <|> superscript <|> subscript <|> symbol <|>
+ argument <|> plain <|> misc
+
+whitespace = many1 space >> return []
+
+symbol = try $ do
+ char '\\'
+ res <- many1 letter
+ case lookup res teXsymbols of
+ Just m -> return [Str m]
+ Nothing -> return [Str $ "\\" ++ res]
+
+argument = try $ do
+ char '{'
+ res <- many mathPart
+ char '}'
+ return $ if null res
+ then [Str " "]
+ else [Str "{"] ++ concat res ++ [Str "}"]
+
+plain = do
+ res <- many1 alphaNum
+ return $ [Emph [Str res]]
+
+misc = do
+ res <- noneOf "{}\\"
+ return [Str [res]]
+
+scriptArg = try $ do
+ (try (do{char '{'; r <- many mathPart; char '}'; return $ concat r}))
+ <|> symbol
+ <|> (do{c <- (letter <|> digit); return [Str [c]]})
+
+superscript = try $ do
+ char '^'
+ arg <- scriptArg
+ return [Superscript arg]
+
+subscript = try $ do
+ char '_'
+ arg <- scriptArg
+ return [Subscript arg]
+
+withThinSpace str = "\x2009" ++ str ++ "\x2009"
+
+teXsymbols =
+ [("alpha","\x3B1")
+ ,("beta", "\x3B2")
+ ,("chi", "\x3C7")
+ ,("delta", "\x3B4")
+ ,("Delta", "\x394")
+ ,("epsilon", "\x3B5")
+ ,("varepsilon", "\x25B")
+ ,("eta", "\x3B7")
+ ,("gamma", "\x3B3")
+ ,("Gamma", "\x393")
+ ,("iota", "\x3B9")
+ ,("kappa", "\x3BA")
+ ,("lambda", "\x3BB")
+ ,("Lambda", "\x39B")
+ ,("mu", "\x3BC")
+ ,("nu", "\x3BD")
+ ,("omega", "\x3C9")
+ ,("Omega", "\x3A9")
+ ,("phi", "\x3C6")
+ ,("varphi", "\x3D5")
+ ,("Phi", "\x3A6")
+ ,("pi", "\x3C0")
+ ,("Pi", "\x3A0")
+ ,("psi", "\x3C8")
+ ,("Psi", "\x3A8")
+ ,("rho", "\x3C1")
+ ,("sigma", "\x3C3")
+ ,("Sigma", "\x3A3")
+ ,("tau", "\x3C4")
+ ,("theta", "\x3B8")
+ ,("vartheta", "\x3D1")
+ ,("Theta", "\x398")
+ ,("upsilon", "\x3C5")
+ ,("xi", "\x3BE")
+ ,("Xi", "\x39E")
+ ,("zeta", "\x3B6")
+ ,("ne", "\x2260")
+ ,("lt", withThinSpace "<")
+ ,("le", withThinSpace "\x2264")
+ ,("leq", withThinSpace "\x2264")
+ ,("ge", withThinSpace "\x2265")
+ ,("geq", withThinSpace "\x2265")
+ ,("prec", withThinSpace "\x227A")
+ ,("succ", withThinSpace "\x227B")
+ ,("preceq", withThinSpace "\x2AAF")
+ ,("succeq", withThinSpace "\x2AB0")
+ ,("in", withThinSpace "\x2208")
+ ,("notin", withThinSpace "\x2209")
+ ,("subset", withThinSpace "\x2282")
+ ,("supset", withThinSpace "\x2283")
+ ,("subseteq", withThinSpace "\x2286")
+ ,("supseteq", withThinSpace "\x2287")
+ ,("equiv", withThinSpace "\x2261")
+ ,("cong", withThinSpace "\x2245")
+ ,("approx", withThinSpace "\x2248")
+ ,("propto", withThinSpace "\x221D")
+ ,("cdot", withThinSpace "\x22C5")
+ ,("star", withThinSpace "\x22C6")
+ ,("backslash", "\\")
+ ,("times", withThinSpace "\x00D7")
+ ,("divide", withThinSpace "\x00F7")
+ ,("circ", withThinSpace "\x2218")
+ ,("oplus", withThinSpace "\x2295")
+ ,("otimes", withThinSpace "\x2297")
+ ,("odot", withThinSpace "\x2299")
+ ,("sum", "\x2211")
+ ,("prod", "\x220F")
+ ,("wedge", withThinSpace "\x2227")
+ ,("bigwedge", withThinSpace "\x22C0")
+ ,("vee", withThinSpace "\x2228")
+ ,("bigvee", withThinSpace "\x22C1")
+ ,("cap", withThinSpace "\x2229")
+ ,("bigcap", withThinSpace "\x22C2")
+ ,("cup", withThinSpace "\x222A")
+ ,("bigcup", withThinSpace "\x22C3")
+ ,("neg", "\x00AC")
+ ,("implies", withThinSpace "\x21D2")
+ ,("iff", withThinSpace "\x21D4")
+ ,("forall", "\x2200")
+ ,("exists", "\x2203")
+ ,("bot", "\x22A5")
+ ,("top", "\x22A4")
+ ,("vdash", "\x22A2")
+ ,("models", withThinSpace "\x22A8")
+ ,("uparrow", "\x2191")
+ ,("downarrow", "\x2193")
+ ,("rightarrow", withThinSpace "\x2192")
+ ,("to", withThinSpace "\x2192")
+ ,("rightarrowtail", "\x21A3")
+ ,("twoheadrightarrow", withThinSpace "\x21A0")
+ ,("twoheadrightarrowtail", withThinSpace "\x2916")
+ ,("mapsto", withThinSpace "\x21A6")
+ ,("leftarrow", withThinSpace "\x2190")
+ ,("leftrightarrow", withThinSpace "\x2194")
+ ,("Rightarrow", withThinSpace "\x21D2")
+ ,("Leftarrow", withThinSpace "\x21D0")
+ ,("Leftrightarrow", withThinSpace "\x21D4")
+ ,("partial", "\x2202")
+ ,("nabla", "\x2207")
+ ,("pm", "\x00B1")
+ ,("emptyset", "\x2205")
+ ,("infty", "\x221E")
+ ,("aleph", "\x2135")
+ ,("ldots", "...")
+ ,("therefore", "\x2234")
+ ,("angle", "\x2220")
+ ,("quad", "\x00A0\x00A0")
+ ,("cdots", "\x22EF")
+ ,("vdots", "\x22EE")
+ ,("ddots", "\x22F1")
+ ,("diamond", "\x22C4")
+ ,("Box", "\x25A1")
+ ,("lfloor", "\x230A")
+ ,("rfloor", "\x230B")
+ ,("lceiling", "\x2308")
+ ,("rceiling", "\x2309")
+ ,("langle", "\x2329")
+ ,("rangle", "\x232A")
+ ,("{", "{")
+ ,("}", "}")
+ ,("[", "[")
+ ,("]", "]")
+ ,("|", "|")
+ ,("||", "||")
+ ]
+
diff --git a/Text/Pandoc/Writers/Docbook.hs b/Text/Pandoc/Writers/Docbook.hs
index 2cad0ca39..f0fde18a4 100644
--- a/Text/Pandoc/Writers/Docbook.hs
+++ b/Text/Pandoc/Writers/Docbook.hs
@@ -30,6 +30,7 @@ Conversion of 'Pandoc' documents to Docbook XML.
module Text.Pandoc.Writers.Docbook ( writeDocbook) where
import Text.Pandoc.Definition
import Text.Pandoc.Shared
+import Text.Pandoc.Readers.TeXMath
import Data.List ( isPrefixOf, drop )
import Text.PrettyPrint.HughesPJ hiding ( Str )
@@ -274,7 +275,7 @@ inlineToDocbook opts EmDash = text "&#8212;"
inlineToDocbook opts EnDash = text "&#8211;"
inlineToDocbook opts (Code str) =
inTagsSimple "literal" $ text (escapeStringForXML str)
-inlineToDocbook opts (Math str) = inlineToDocbook opts (Code str)
+inlineToDocbook opts (Math str) = inlinesToDocbook opts $ readTeXMath str
inlineToDocbook opts (TeX str) = empty
inlineToDocbook opts (HtmlInline str) = empty
inlineToDocbook opts LineBreak = text $ "<literallayout></literallayout>"
diff --git a/Text/Pandoc/Writers/HTML.hs b/Text/Pandoc/Writers/HTML.hs
index 881e3c07c..70814eb15 100644
--- a/Text/Pandoc/Writers/HTML.hs
+++ b/Text/Pandoc/Writers/HTML.hs
@@ -32,6 +32,7 @@ import Text.Pandoc.Definition
import Text.Pandoc.ASCIIMathML
import Text.Pandoc.CharacterReferences ( decodeCharacterReferences )
import Text.Pandoc.Shared
+import Text.Pandoc.Readers.TeXMath
import Text.Regex ( mkRegex, matchRegex )
import Numeric ( showHex )
import Data.Char ( ord, toLower )
@@ -401,16 +402,16 @@ inlineToHtml opts inline =
in do contents <- inlineListToHtml opts lst
return $ leftQuote +++ contents +++ rightQuote
(Math str) -> modify (\st -> st {stMath = True}) >>
- (return $ case writerHTMLMathMethod opts of
- ASCIIMathML _ ->
- stringToHtml ("$" ++ str ++ "$")
- MimeTeX url ->
- image ! [src (url ++ "?" ++ str),
+ (case writerHTMLMathMethod opts of
+ ASCIIMathML _ ->
+ return $ stringToHtml ("$" ++ str ++ "$")
+ MimeTeX url ->
+ return $ image ! [src (url ++ "?" ++ str),
alt str, title str]
- GladTeX ->
- tag "eq" << str
- PlainMath ->
- stringToHtml str)
+ GladTeX ->
+ return $ tag "eq" << str
+ PlainMath ->
+ inlineListToHtml opts (readTeXMath str))
(TeX str) -> return noHtml
(HtmlInline str) -> return $ primHtml str
(Link [Code str] (src,tit)) | "mailto:" `isPrefixOf` src ->
diff --git a/Text/Pandoc/Writers/Man.hs b/Text/Pandoc/Writers/Man.hs
index 899cd9f57..bd170f6ba 100644
--- a/Text/Pandoc/Writers/Man.hs
+++ b/Text/Pandoc/Writers/Man.hs
@@ -30,7 +30,8 @@ Conversion of 'Pandoc' documents to groff man page format.
-}
module Text.Pandoc.Writers.Man ( writeMan) where
import Text.Pandoc.Definition
-import Text.Pandoc.Shared
+import Text.Pandoc.Shared
+import Text.Pandoc.Readers.TeXMath
import Text.Printf ( printf )
import Data.List ( isPrefixOf, drop, nub, intersperse )
import Text.PrettyPrint.HughesPJ hiding ( Str )
@@ -268,7 +269,7 @@ inlineToMan opts Ellipses = return $ text "\\&..."
inlineToMan opts (Code str) =
return $ text $ "\\f[B]" ++ escapeCode str ++ "\\f[]"
inlineToMan opts (Str str) = return $ text $ escapeString str
-inlineToMan opts (Math str) = return $ text $ escapeCode str
+inlineToMan opts (Math str) = inlineToMan opts (Code str)
inlineToMan opts (TeX str) = return empty
inlineToMan opts (HtmlInline str) = return $ text $ escapeCode str
inlineToMan opts (LineBreak) = return $ text "\n.PD 0\n.P\n.PD\n"
diff --git a/Text/Pandoc/Writers/RST.hs b/Text/Pandoc/Writers/RST.hs
index 4a7242d1f..7dd99f2ea 100644
--- a/Text/Pandoc/Writers/RST.hs
+++ b/Text/Pandoc/Writers/RST.hs
@@ -32,6 +32,7 @@ reStructuredText: <http://docutils.sourceforge.net/rst.html>
module Text.Pandoc.Writers.RST ( writeRST) where
import Text.Pandoc.Definition
import Text.Pandoc.Shared
+import Text.Pandoc.Readers.TeXMath
import Text.Pandoc.Blocks
import Data.List ( isPrefixOf, isSuffixOf, drop, intersperse )
import Text.PrettyPrint.HughesPJ hiding ( Str )
@@ -151,10 +152,6 @@ blockToRST :: WriterOptions -- ^ Options
-> State WriterState Doc
blockToRST opts Null = return empty
blockToRST opts (Plain inlines) = wrappedRST opts inlines
-blockToRST opts (Para [Math str]) =
- let str' = if "\n" `isSuffixOf` str then str ++ "\n" else str ++ "\n\n" in
- return $ hang (text "\n.. raw:: latex\n") 3 $ text "\\[" <>
- (vcat $ map text (lines str')) <> text "\\]"
blockToRST opts (Para inlines) = do
contents <- wrappedRST opts inlines
return $ contents <> text "\n"
@@ -286,7 +283,7 @@ inlineToRST opts Apostrophe = return $ char '\''
inlineToRST opts Ellipses = return $ text "..."
inlineToRST opts (Code str) = return $ text $ "``" ++ str ++ "``"
inlineToRST opts (Str str) = return $ text $ escapeString str
-inlineToRST opts (Math str) = return $ char '$' <> text str <> char '$'
+inlineToRST opts (Math str) = return $ text $ "$" ++ str ++ "$"
inlineToRST opts (TeX str) = return empty
inlineToRST opts (HtmlInline str) = return empty
inlineToRST opts (LineBreak) = return $ char ' ' -- RST doesn't have linebreaks
diff --git a/Text/Pandoc/Writers/RTF.hs b/Text/Pandoc/Writers/RTF.hs
index 9c5e6cbd3..64d73a30f 100644
--- a/Text/Pandoc/Writers/RTF.hs
+++ b/Text/Pandoc/Writers/RTF.hs
@@ -30,6 +30,7 @@ Conversion of 'Pandoc' documents to RTF (rich text format).
module Text.Pandoc.Writers.RTF ( writeRTF ) where
import Text.Pandoc.Definition
import Text.Pandoc.Shared
+import Text.Pandoc.Readers.TeXMath
import Text.Regex ( matchRegexAll, mkRegex )
import Data.List ( isSuffixOf )
import Data.Char ( ord )
@@ -272,7 +273,7 @@ inlineToRTF EmDash = "\\u8212-"
inlineToRTF EnDash = "\\u8211-"
inlineToRTF (Code str) = "{\\f1 " ++ (codeStringToRTF str) ++ "} "
inlineToRTF (Str str) = stringToRTF str
-inlineToRTF (Math str) = latexToRTF str
+inlineToRTF (Math str) = inlineListToRTF $ readTeXMath str
inlineToRTF (TeX str) = ""
inlineToRTF (HtmlInline str) = ""
inlineToRTF (LineBreak) = "\\line "