diff options
Diffstat (limited to 'src/Text/Pandoc/Readers')
-rw-r--r-- | src/Text/Pandoc/Readers/HTML.hs | 8 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/LaTeX.hs | 10 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/Markdown.hs | 5 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/RST.hs | 3 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/TeXMath.hs | 2 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/Textile.hs | 4 |
6 files changed, 19 insertions, 13 deletions
diff --git a/src/Text/Pandoc/Readers/HTML.hs b/src/Text/Pandoc/Readers/HTML.hs index d267a4ff2..18e3113d3 100644 --- a/src/Text/Pandoc/Readers/HTML.hs +++ b/src/Text/Pandoc/Readers/HTML.hs @@ -338,9 +338,13 @@ pImage = do pCode :: TagParser [Inline] pCode = try $ do - (TagOpen open _) <- pSatisfy $ tagOpen (`elem` ["code","tt"]) (const True) + (TagOpen open attr) <- pSatisfy $ tagOpen (`elem` ["code","tt"]) (const True) result <- manyTill pAnyTag (pCloses open) - return [Code $ intercalate " " $ lines $ innerText result] + let ident = fromMaybe "" $ lookup "id" attr + let classes = words $ fromMaybe [] $ lookup "class" attr + let rest = filter (\(x,_) -> x /= "id" && x /= "class") attr + return [Code (ident,classes,rest) + $ intercalate " " $ lines $ innerText result] pRawHtmlInline :: TagParser [Inline] pRawHtmlInline = do diff --git a/src/Text/Pandoc/Readers/LaTeX.hs b/src/Text/Pandoc/Readers/LaTeX.hs index d20acac92..83b74a489 100644 --- a/src/Text/Pandoc/Readers/LaTeX.hs +++ b/src/Text/Pandoc/Readers/LaTeX.hs @@ -710,27 +710,27 @@ code1 = try $ do string "\\verb" marker <- anyChar result <- manyTill anyChar (char marker) - return $ Code $ removeLeadingTrailingSpace result + return $ Code nullAttr $ removeLeadingTrailingSpace result code2 :: GenParser Char st Inline code2 = try $ do string "\\texttt{" result <- manyTill (noneOf "\\\n~$%^&{}") (char '}') - return $ Code result + return $ Code nullAttr result code3 :: GenParser Char st Inline code3 = try $ do string "\\lstinline" marker <- anyChar result <- manyTill anyChar (char marker) - return $ Code $ removeLeadingTrailingSpace result + return $ Code nullAttr $ removeLeadingTrailingSpace result lhsInlineCode :: GenParser Char ParserState Inline lhsInlineCode = try $ do failUnlessLHS char '|' result <- manyTill (noneOf "|\n") (char '|') - return $ Code result + return $ Code ("",["haskell"],[]) result emph :: GenParser Char ParserState Inline emph = try $ oneOfStrings [ "\\emph{", "\\textit{" ] >> @@ -861,7 +861,7 @@ url :: GenParser Char ParserState Inline url = try $ do string "\\url" url' <- charsInBalanced '{' '}' - return $ Link [Code url'] (escapeURI url', "") + return $ Link [Code ("",["url"],[]) url'] (escapeURI url', "") link :: GenParser Char ParserState Inline link = try $ do diff --git a/src/Text/Pandoc/Readers/Markdown.hs b/src/Text/Pandoc/Readers/Markdown.hs index ed04ee034..1b9094ab9 100644 --- a/src/Text/Pandoc/Readers/Markdown.hs +++ b/src/Text/Pandoc/Readers/Markdown.hs @@ -977,7 +977,8 @@ code = try $ do (char '\n' >> notFollowedBy' blankline >> return " ")) (try (skipSpaces >> count (length starts) (char '`') >> notFollowedBy (char '`'))) - return $ Code $ removeLeadingTrailingSpace $ concat result + attr <- option ([],[],[]) (try $ optional whitespace >> attributes) + return $ Code attr $ removeLeadingTrailingSpace $ concat result mathWord :: GenParser Char st [Char] mathWord = liftM concat $ many1 mathChunk @@ -1163,7 +1164,7 @@ autoLink = try $ do st <- getState return $ if stateStrict st then Link [Str orig] (src, "") - else Link [Code orig] (src, "") + else Link [Code ("",["url"],[]) orig] (src, "") image :: GenParser Char ParserState Inline image = try $ do diff --git a/src/Text/Pandoc/Readers/RST.hs b/src/Text/Pandoc/Readers/RST.hs index 16ae384d1..582766d38 100644 --- a/src/Text/Pandoc/Readers/RST.hs +++ b/src/Text/Pandoc/Readers/RST.hs @@ -746,7 +746,8 @@ code :: GenParser Char ParserState Inline code = try $ do string "``" result <- manyTill anyChar (try (string "``")) - return $ Code $ removeLeadingTrailingSpace $ intercalate " " $ lines result + return $ Code nullAttr + $ removeLeadingTrailingSpace $ intercalate " " $ lines result emph :: GenParser Char ParserState Inline emph = enclosed (char '*') (char '*') inline >>= diff --git a/src/Text/Pandoc/Readers/TeXMath.hs b/src/Text/Pandoc/Readers/TeXMath.hs index 8c9fe2c7e..b9a46e8ff 100644 --- a/src/Text/Pandoc/Readers/TeXMath.hs +++ b/src/Text/Pandoc/Readers/TeXMath.hs @@ -90,7 +90,7 @@ expToInlines (EUp x y) = expToInlines (ESuper x y) expToInlines (EDownup x y z) = expToInlines (ESubsup x y z) expToInlines (EText "normal" x) = Just [Str x] expToInlines (EText "bold" x) = Just [Strong [Str x]] -expToInlines (EText "monospace" x) = Just [Code x] +expToInlines (EText "monospace" x) = Just [Code nullAttr x] expToInlines (EText "italic" x) = Just [Emph [Str x]] expToInlines (EText _ x) = Just [Str x] expToInlines (EOver (EGrouped [EIdentifier [c]]) (ESymbol Accent [accent])) = diff --git a/src/Text/Pandoc/Readers/Textile.hs b/src/Text/Pandoc/Readers/Textile.hs index 714cac9f4..19357b343 100644 --- a/src/Text/Pandoc/Readers/Textile.hs +++ b/src/Text/Pandoc/Readers/Textile.hs @@ -494,13 +494,13 @@ code :: GenParser Char ParserState Inline code = code1 <|> code2 code1 :: GenParser Char ParserState Inline -code1 = surrounded (char '@') anyChar >>= return . Code +code1 = surrounded (char '@') anyChar >>= return . Code nullAttr code2 :: GenParser Char ParserState Inline code2 = do htmlTag (tagOpen (=="tt") null) result' <- manyTill anyChar (try $ htmlTag $ tagClose (=="tt")) - return $ Code result' + return $ Code nullAttr result' -- | Html / CSS attributes attributes :: GenParser Char ParserState String |