aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Readers
diff options
context:
space:
mode:
Diffstat (limited to 'src/Text/Pandoc/Readers')
-rw-r--r--src/Text/Pandoc/Readers/LaTeX.hs8
-rw-r--r--src/Text/Pandoc/Readers/Markdown.hs5
-rw-r--r--src/Text/Pandoc/Readers/TeXMath.hs84
3 files changed, 6 insertions, 91 deletions
diff --git a/src/Text/Pandoc/Readers/LaTeX.hs b/src/Text/Pandoc/Readers/LaTeX.hs
index 028d83e24..5d73134cd 100644
--- a/src/Text/Pandoc/Readers/LaTeX.hs
+++ b/src/Text/Pandoc/Readers/LaTeX.hs
@@ -38,7 +38,6 @@ import Text.Pandoc.Definition
import Text.Pandoc.Walk
import Text.Pandoc.Shared
import Text.Pandoc.Options
-import Text.Pandoc.Biblio (processBiblio)
import Text.Pandoc.Parsing hiding ((<|>), many, optional, space)
import qualified Text.Pandoc.UTF8 as UTF8
import Data.Char ( chr, ord )
@@ -47,6 +46,7 @@ import Text.Pandoc.Builder
import Data.Char (isLetter)
import Control.Applicative
import Data.Monoid
+import Data.Maybe (fromMaybe)
import System.Environment (getEnv)
import System.FilePath (replaceExtension, (</>))
import Data.List (intercalate, intersperse)
@@ -67,9 +67,7 @@ parseLaTeX = do
eof
st <- getState
let meta = stateMeta st
- refs <- getOption readerReferences
- mbsty <- getOption readerCitationStyle
- let (Pandoc _ bs') = processBiblio mbsty refs $ doc bs
+ let (Pandoc _ bs') = doc bs
return $ Pandoc meta bs'
type LP = Parser [Char] ParserState
@@ -903,7 +901,7 @@ environments = M.fromList
lookup "numbers" options == Just "left" ]
++ maybe [] (:[]) (lookup "language" options
>>= fromListingsLanguage)
- let attr = ("",classes,kvs)
+ let attr = (fromMaybe "" (lookup "label" options),classes,kvs)
codeBlockWith attr <$> (verbEnv "lstlisting"))
, ("minted", do options <- option [] keyvals
lang <- grouped (many1 $ satisfy (/='}'))
diff --git a/src/Text/Pandoc/Readers/Markdown.hs b/src/Text/Pandoc/Readers/Markdown.hs
index 05662d9b5..658335202 100644
--- a/src/Text/Pandoc/Readers/Markdown.hs
+++ b/src/Text/Pandoc/Readers/Markdown.hs
@@ -54,7 +54,6 @@ import Text.Pandoc.Parsing hiding (tableWith)
import Text.Pandoc.Readers.LaTeX ( rawLaTeXInline, rawLaTeXBlock )
import Text.Pandoc.Readers.HTML ( htmlTag, htmlInBalanced, isInlineTag, isBlockTag,
isTextTag, isCommentTag )
-import Text.Pandoc.Biblio (processBiblio)
import Data.Monoid (mconcat, mempty)
import Control.Applicative ((<$>), (<*), (*>), (<$))
import Control.Monad
@@ -327,9 +326,7 @@ parseMarkdown = do
st <- getState
let meta = runF (stateMeta' st) st
let Pandoc _ bs = B.doc $ runF blocks st
- mbsty <- getOption readerCitationStyle
- refs <- getOption readerReferences
- return $ processBiblio mbsty refs $ Pandoc meta bs
+ return $ Pandoc meta bs
addWarning :: Maybe SourcePos -> String -> MarkdownParser ()
addWarning mbpos msg =
diff --git a/src/Text/Pandoc/Readers/TeXMath.hs b/src/Text/Pandoc/Readers/TeXMath.hs
index fe49a992e..1f7088f72 100644
--- a/src/Text/Pandoc/Readers/TeXMath.hs
+++ b/src/Text/Pandoc/Readers/TeXMath.hs
@@ -30,93 +30,13 @@ Conversion of TeX math to a list of 'Pandoc' inline elements.
module Text.Pandoc.Readers.TeXMath ( readTeXMath ) where
import Text.Pandoc.Definition
-import Text.TeXMath.Types
-import Text.TeXMath.Parser
+import Text.TeXMath
-- | 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.
readTeXMath :: String -- ^ String to parse (assumes @'\n'@ line endings)
-> [Inline]
-readTeXMath inp = case texMathToPandoc inp of
+readTeXMath inp = case texMathToPandoc DisplayInline inp of
Left _ -> [Str ("$" ++ inp ++ "$")]
Right res -> res
-
-texMathToPandoc :: String -> Either String [Inline]
-texMathToPandoc inp = inp `seq`
- case parseFormula inp of
- Left err -> Left err
- Right exps -> case expsToInlines exps of
- Nothing -> Left "Formula too complex for [Inline]"
- Just r -> Right r
-
-expsToInlines :: [Exp] -> Maybe [Inline]
-expsToInlines xs = do
- res <- mapM expToInlines xs
- return (concat res)
-
-expToInlines :: Exp -> Maybe [Inline]
-expToInlines (ENumber s) = Just [Str s]
-expToInlines (EIdentifier s) = Just [Emph [Str s]]
-expToInlines (EMathOperator s) = Just [Str s]
-expToInlines (ESymbol t s) = Just $ addSpace t (Str s)
- where addSpace Op x = [x, thinspace]
- addSpace Bin x = [medspace, x, medspace]
- addSpace Rel x = [widespace, x, widespace]
- addSpace Pun x = [x, thinspace]
- addSpace _ x = [x]
- thinspace = Str "\x2006"
- medspace = Str "\x2005"
- widespace = Str "\x2004"
-expToInlines (EStretchy x) = expToInlines x
-expToInlines (EDelimited start end xs) = do
- xs' <- mapM expToInlines xs
- return $ [Str start] ++ concat xs' ++ [Str end]
-expToInlines (EGrouped xs) = expsToInlines xs
-expToInlines (ESpace "0.167em") = Just [Str "\x2009"]
-expToInlines (ESpace "0.222em") = Just [Str "\x2005"]
-expToInlines (ESpace "0.278em") = Just [Str "\x2004"]
-expToInlines (ESpace "0.333em") = Just [Str "\x2004"]
-expToInlines (ESpace "1em") = Just [Str "\x2001"]
-expToInlines (ESpace "2em") = Just [Str "\x2001\x2001"]
-expToInlines (ESpace _) = Just [Str " "]
-expToInlines (EBinary _ _ _) = Nothing
-expToInlines (ESub x y) = do
- x' <- expToInlines x
- y' <- expToInlines y
- return $ x' ++ [Subscript y']
-expToInlines (ESuper x y) = do
- x' <- expToInlines x
- y' <- expToInlines y
- return $ x' ++ [Superscript y']
-expToInlines (ESubsup x y z) = do
- x' <- expToInlines x
- y' <- expToInlines y
- z' <- expToInlines z
- return $ x' ++ [Subscript y'] ++ [Superscript z']
-expToInlines (EDown x y) = expToInlines (ESub x y)
-expToInlines (EUp x y) = expToInlines (ESuper x y)
-expToInlines (EDownup x y z) = expToInlines (ESubsup x y z)
-expToInlines (EText TextNormal x) = Just [Str x]
-expToInlines (EText TextBold x) = Just [Strong [Str x]]
-expToInlines (EText TextMonospace x) = Just [Code nullAttr x]
-expToInlines (EText TextItalic x) = Just [Emph [Str x]]
-expToInlines (EText _ x) = Just [Str x]
-expToInlines (EOver (EGrouped [EIdentifier [c]]) (ESymbol Accent [accent])) =
- case accent of
- '\x203E' -> Just [Emph [Str [c,'\x0304']]] -- bar
- '\x00B4' -> Just [Emph [Str [c,'\x0301']]] -- acute
- '\x0060' -> Just [Emph [Str [c,'\x0300']]] -- grave
- '\x02D8' -> Just [Emph [Str [c,'\x0306']]] -- breve
- '\x02C7' -> Just [Emph [Str [c,'\x030C']]] -- check
- '.' -> Just [Emph [Str [c,'\x0307']]] -- dot
- '\x00B0' -> Just [Emph [Str [c,'\x030A']]] -- ring
- '\x20D7' -> Just [Emph [Str [c,'\x20D7']]] -- arrow right
- '\x20D6' -> Just [Emph [Str [c,'\x20D6']]] -- arrow left
- '\x005E' -> Just [Emph [Str [c,'\x0302']]] -- hat
- '\x0302' -> Just [Emph [Str [c,'\x0302']]] -- hat
- '~' -> Just [Emph [Str [c,'\x0303']]] -- tilde
- _ -> Nothing
-expToInlines _ = Nothing
-
-