Use generic attributes type, not a string, for CodeBlocks.
git-svn-id: https://pandoc.googlecode.com/svn/trunk@1209 788f1e2b-df1e-0410-8736-df70ead52e1b
This commit is contained in:
parent
705340824d
commit
614547b38e
6 changed files with 45 additions and 19 deletions
|
@ -62,11 +62,14 @@ data ListNumberDelim = DefaultDelim
|
|||
| OneParen
|
||||
| TwoParens deriving (Eq, Show, Read)
|
||||
|
||||
-- | Attributes.
|
||||
type Attr = (String, [String], [(String, String)]) -- ^ Identifier, classes, key-value pairs
|
||||
|
||||
-- | Block element.
|
||||
data Block
|
||||
= Plain [Inline] -- ^ Plain text, not a paragraph
|
||||
| Para [Inline] -- ^ Paragraph
|
||||
| CodeBlock String String -- ^ Code block (literal) with class
|
||||
| CodeBlock Attr String -- ^ Code block (literal) with attributes
|
||||
| RawHtml String -- ^ Raw HTML block (literal)
|
||||
| BlockQuote [Block] -- ^ Block quote (list of blocks)
|
||||
| OrderedList ListAttributes [[Block]] -- ^ Ordered list (attributes
|
||||
|
|
|
@ -407,7 +407,7 @@ codeBlock = try $ do
|
|||
let result''' = if "\n" `isSuffixOf` result''
|
||||
then init result''
|
||||
else result''
|
||||
return $ CodeBlock "" $ decodeCharacterReferences result'''
|
||||
return $ CodeBlock ("",[],[]) $ decodeCharacterReferences result'''
|
||||
|
||||
--
|
||||
-- block quotes
|
||||
|
|
|
@ -182,14 +182,14 @@ codeBlock1 = try $ do
|
|||
-- leading space
|
||||
contents <- manyTill anyChar (try (string "\\end{verbatim}"))
|
||||
spaces
|
||||
return $ CodeBlock "" (stripTrailingNewlines contents)
|
||||
return $ CodeBlock ("",[],[]) (stripTrailingNewlines contents)
|
||||
|
||||
codeBlock2 = try $ do
|
||||
string "\\begin{Verbatim}" -- used by fancyvrb package
|
||||
optional blanklines
|
||||
contents <- manyTill anyChar (try (string "\\end{Verbatim}"))
|
||||
spaces
|
||||
return $ CodeBlock "" (stripTrailingNewlines contents)
|
||||
return $ CodeBlock ("",[],[]) (stripTrailingNewlines contents)
|
||||
|
||||
--
|
||||
-- block quotes
|
||||
|
|
|
@ -303,25 +303,48 @@ codeBlockDelimiter len = try $ do
|
|||
Nothing -> count 3 (char '~') >> many (char '~') >>=
|
||||
return . (+ 3) . length
|
||||
many spaceChar
|
||||
lang <- option "" classAttributes
|
||||
attr <- option ([],[],[]) attributes
|
||||
blankline
|
||||
return (size, lang)
|
||||
return (size, attr)
|
||||
|
||||
classAttributes = try $ do
|
||||
attributes = try $ do
|
||||
char '{'
|
||||
many spaceChar
|
||||
attrs <- many $ try $ do char '.'
|
||||
attr <- many1 alphaNum
|
||||
many spaceChar
|
||||
return attr
|
||||
attrs <- many (attribute >>~ many spaceChar)
|
||||
char '}'
|
||||
return $ unwords attrs
|
||||
let (ids, classes, keyvals) = unzip3 attrs
|
||||
let id = if null ids then "" else head ids
|
||||
return (id, concat classes, concat keyvals)
|
||||
|
||||
attribute = identifierAttr <|> classAttr <|> keyValAttr
|
||||
|
||||
identifier = do
|
||||
first <- letter
|
||||
rest <- many alphaNum
|
||||
return (first:rest)
|
||||
|
||||
identifierAttr = try $ do
|
||||
char '#'
|
||||
result <- identifier
|
||||
return (result,[],[])
|
||||
|
||||
classAttr = try $ do
|
||||
char '.'
|
||||
result <- identifier
|
||||
return ("",[result],[])
|
||||
|
||||
keyValAttr = try $ do
|
||||
key <- identifier
|
||||
char '='
|
||||
char '"'
|
||||
val <- manyTill (noneOf "\n") (char '"')
|
||||
return ("",[],[(key,val)])
|
||||
|
||||
codeBlockDelimited = try $ do
|
||||
(size, lang) <- codeBlockDelimiter Nothing
|
||||
(size, attr) <- codeBlockDelimiter Nothing
|
||||
contents <- manyTill anyLine (codeBlockDelimiter (Just size))
|
||||
blanklines
|
||||
return $ CodeBlock lang $ joinWithSep "\n" contents
|
||||
return $ CodeBlock attr $ joinWithSep "\n" contents
|
||||
|
||||
codeBlockIndented = do
|
||||
contents <- many1 (indentedLine <|>
|
||||
|
@ -329,7 +352,7 @@ codeBlockIndented = do
|
|||
l <- indentedLine
|
||||
return $ b ++ l))
|
||||
optional blanklines
|
||||
return $ CodeBlock "" $ stripTrailingNewlines $ concat contents
|
||||
return $ CodeBlock ("",[],[]) $ stripTrailingNewlines $ concat contents
|
||||
|
||||
--
|
||||
-- block quotes
|
||||
|
|
|
@ -304,7 +304,7 @@ indentedBlock = do
|
|||
codeBlock = try $ do
|
||||
codeBlockStart
|
||||
result <- indentedBlock
|
||||
return $ CodeBlock "" $ stripTrailingNewlines result
|
||||
return $ CodeBlock ("",[],[]) $ stripTrailingNewlines result
|
||||
|
||||
--
|
||||
-- raw html
|
||||
|
|
|
@ -263,8 +263,8 @@ blockToHtml opts (Plain lst) = inlineListToHtml opts lst
|
|||
blockToHtml opts (Para lst) = inlineListToHtml opts lst >>= (return . paragraph)
|
||||
blockToHtml opts (RawHtml str) = return $ primHtml str
|
||||
blockToHtml opts (HorizontalRule) = return $ hr
|
||||
blockToHtml opts (CodeBlock lang str) = return $
|
||||
pre ! (if null lang then [] else [theclass lang]) $
|
||||
blockToHtml opts (CodeBlock (_,classes,_) str) = return $
|
||||
pre ! (if null classes then [] else [theclass $ unwords classes]) $
|
||||
thecode << (str ++ "\n") -- the final \n for consistency with Markdown.pl
|
||||
blockToHtml opts (BlockQuote blocks) =
|
||||
-- in S5, treat list in blockquote specially
|
||||
|
|
Loading…
Reference in a new issue