aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--README18
-rw-r--r--src/Text/Pandoc/Options.hs1
-rw-r--r--src/Text/Pandoc/Readers/Markdown.hs45
-rw-r--r--src/Text/Pandoc/Writers/HTML.hs8
-rw-r--r--src/Text/Pandoc/Writers/LaTeX.hs5
-rw-r--r--src/Text/Pandoc/Writers/Markdown.hs4
-rw-r--r--tests/Tests/Readers/Markdown.hs2
-rw-r--r--tests/tables.latex9
8 files changed, 59 insertions, 33 deletions
diff --git a/README b/README
index 35e5b0504..bc80f1b5a 100644
--- a/README
+++ b/README
@@ -1181,6 +1181,8 @@ row of tildes or backticks at the start and end:
~~~~~~~~~~
~~~~~~~~~~~~~~~~
+**Extension: `fenced_code_attributes`**
+
Optionally, you may attach attributes to the code block using
this syntax:
@@ -1217,6 +1219,11 @@ This is equivalent to:
qsort [] = []
```
+If the `fenced_code_attributes` extension is disabled, but
+input contains class attribute(s) for the codeblock, the first
+class attribute will be printed after the opening fence as a bare
+word.
+
To prevent all highlighting, use the `--no-highlight` flag.
To set the highlighting style, use `--highlight-style`.
@@ -1842,7 +1849,14 @@ A YAML metadata block is a valid YAML object, delimited by a line of three
hyphens (`---`) at the top and a line of three hyphens (`---`) or three dots
(`...`) at the bottom. A YAML metadata block may occur anywhere in the
document, but if it is not at the beginning, it must be preceded by a blank
-line.
+line. (Note that, because of the way pandoc concatenates input files when
+several are provided, you may also keep the metadata in a separate YAML file
+and pass it to pandoc as an argument, along with your markdown files:
+
+ pandoc chap1.md chap2.md chap3.md metadata.yaml -s -o book.html
+
+Just be sure that the YAML file begins with `---` and ends with `---` or
+`...`.)
Metadata will be taken from the fields of the YAML object and added to any
existing document metadata. Metadata can contain lists and objects (nested
@@ -2627,7 +2641,7 @@ variants are supported:
`markdown_github` (Github-flavored Markdown)
: `pipe_tables`, `raw_html`, `tex_math_single_backslash`,
- `fenced_code_blocks`, `fenced_code_attributes`, `auto_identifiers`,
+ `fenced_code_blocks`, `auto_identifiers`,
`ascii_identifiers`, `backtick_code_blocks`, `autolink_bare_uris`,
`intraword_underscores`, `strikeout`, `hard_line_breaks`
diff --git a/src/Text/Pandoc/Options.hs b/src/Text/Pandoc/Options.hs
index b7a3a4b7b..8580a6914 100644
--- a/src/Text/Pandoc/Options.hs
+++ b/src/Text/Pandoc/Options.hs
@@ -163,7 +163,6 @@ githubMarkdownExtensions = Set.fromList
, Ext_raw_html
, Ext_tex_math_single_backslash
, Ext_fenced_code_blocks
- , Ext_fenced_code_attributes
, Ext_auto_identifiers
, Ext_ascii_identifiers
, Ext_backtick_code_blocks
diff --git a/src/Text/Pandoc/Readers/Markdown.hs b/src/Text/Pandoc/Readers/Markdown.hs
index 80d6698de..5361158cc 100644
--- a/src/Text/Pandoc/Readers/Markdown.hs
+++ b/src/Text/Pandoc/Readers/Markdown.hs
@@ -1436,52 +1436,60 @@ math = (return . B.displayMath <$> (mathDisplay >>= applyMacros'))
enclosure :: Char
-> MarkdownParser (F Inlines)
enclosure c = do
+ -- we can't start an enclosure with _ if after a string and
+ -- the intraword_underscores extension is enabled:
+ guardDisabled Ext_intraword_underscores
+ <|> guard (c == '*')
+ <|> (guard =<< notAfterString)
cs <- many1 (char c)
(return (B.str cs) <>) <$> whitespace
- <|> case length cs of
+ <|> do
+ case length cs of
3 -> three c
2 -> two c mempty
1 -> one c mempty
_ -> return (return $ B.str cs)
+ender :: Char -> Int -> MarkdownParser ()
+ender c n = try $ do
+ count n (char c)
+ guard (c == '*')
+ <|> guardDisabled Ext_intraword_underscores
+ <|> notFollowedBy alphaNum
+
-- Parse inlines til you hit one c or a sequence of two cs.
-- If one c, emit emph and then parse two.
-- If two cs, emit strong and then parse one.
-- Otherwise, emit ccc then the results.
three :: Char -> MarkdownParser (F Inlines)
three c = do
- contents <- mconcat <$> many (notFollowedBy (char c) >> inline)
- (try (string [c,c,c]) >> return ((B.strong . B.emph) <$> contents))
- <|> (try (string [c,c]) >> one c (B.strong <$> contents))
- <|> (char c >> two c (B.emph <$> contents))
+ contents <- mconcat <$> many (notFollowedBy (ender c 1) >> inline)
+ (ender c 3 >> return ((B.strong . B.emph) <$> contents))
+ <|> (ender c 2 >> one c (B.strong <$> contents))
+ <|> (ender c 1 >> two c (B.emph <$> contents))
<|> return (return (B.str [c,c,c]) <> contents)
-- Parse inlines til you hit two c's, and emit strong.
-- If you never do hit two cs, emit ** plus inlines parsed.
two :: Char -> F Inlines -> MarkdownParser (F Inlines)
two c prefix' = do
- let ender = try $ string [c,c]
- contents <- mconcat <$> many (try $ notFollowedBy ender >> inline)
- (ender >> return (B.strong <$> (prefix' <> contents)))
+ contents <- mconcat <$> many (try $ notFollowedBy (ender c 2) >> inline)
+ (ender c 2 >> return (B.strong <$> (prefix' <> contents)))
<|> return (return (B.str [c,c]) <> (prefix' <> contents))
-- Parse inlines til you hit a c, and emit emph.
-- If you never hit a c, emit * plus inlines parsed.
one :: Char -> F Inlines -> MarkdownParser (F Inlines)
one c prefix' = do
- contents <- mconcat <$> many ( (notFollowedBy (char c) >> inline)
+ contents <- mconcat <$> many ( (notFollowedBy (ender c 1) >> inline)
<|> try (string [c,c] >>
- notFollowedBy (char c) >>
+ notFollowedBy (ender c 1) >>
two c mempty) )
- (char c >> return (B.emph <$> (prefix' <> contents)))
+ (ender c 1 >> return (B.emph <$> (prefix' <> contents)))
<|> return (return (B.str [c]) <> (prefix' <> contents))
strongOrEmph :: MarkdownParser (F Inlines)
-strongOrEmph = enclosure '*' <|> (checkIntraword >> enclosure '_')
- where checkIntraword = do
- exts <- getOption readerExtensions
- when (Ext_intraword_underscores `Set.member` exts) $ do
- guard =<< notAfterString
+strongOrEmph = enclosure '*' <|> enclosure '_'
-- | Parses a list of inlines between start and end delimiters.
inlinesBetween :: (Show b)
@@ -1749,12 +1757,17 @@ divHtml :: MarkdownParser (F Blocks)
divHtml = try $ do
guardEnabled Ext_markdown_in_html_blocks
(TagOpen _ attrs, rawtag) <- htmlTag (~== TagOpen "div" [])
+ -- we set stateInHtmlBlock so that closing tags that can be either block or
+ -- inline will not be parsed as inline tags
+ oldInHtmlBlock <- stateInHtmlBlock <$> getState
+ updateState $ \st -> st{ stateInHtmlBlock = Just "div" }
bls <- option "" (blankline >> option "" blanklines)
contents <- mconcat <$>
many (notFollowedBy' (htmlTag (~== TagClose "div")) >> block)
closed <- option False (True <$ htmlTag (~== TagClose "div"))
if closed
then do
+ updateState $ \st -> st{ stateInHtmlBlock = oldInHtmlBlock }
let ident = fromMaybe "" $ lookup "id" attrs
let classes = maybe [] words $ lookup "class" attrs
let keyvals = [(k,v) | (k,v) <- attrs, k /= "id" && k /= "class"]
diff --git a/src/Text/Pandoc/Writers/HTML.hs b/src/Text/Pandoc/Writers/HTML.hs
index 9a26cf2ac..744e88c16 100644
--- a/src/Text/Pandoc/Writers/HTML.hs
+++ b/src/Text/Pandoc/Writers/HTML.hs
@@ -429,9 +429,11 @@ blockToHtml opts (Div attr@(_,classes,_) bs) = do
let contents' = nl opts >> contents >> nl opts
return $
if "notes" `elem` classes
- then case writerSlideVariant opts of
- RevealJsSlides -> addAttrs opts attr $ H5.aside $ contents'
- NoSlides -> addAttrs opts attr $ H.div $ contents'
+ then let opts' = opts{ writerIncremental = False } in
+ -- we don't want incremental output inside speaker notes
+ case writerSlideVariant opts of
+ RevealJsSlides -> addAttrs opts' attr $ H5.aside $ contents'
+ NoSlides -> addAttrs opts' attr $ H.div $ contents'
_ -> mempty
else addAttrs opts attr $ H.div $ contents'
blockToHtml _ (RawBlock f str)
diff --git a/src/Text/Pandoc/Writers/LaTeX.hs b/src/Text/Pandoc/Writers/LaTeX.hs
index 100bf900d..5bbe30fc8 100644
--- a/src/Text/Pandoc/Writers/LaTeX.hs
+++ b/src/Text/Pandoc/Writers/LaTeX.hs
@@ -471,19 +471,18 @@ blockToLaTeX (Table caption aligns widths heads rows) = do
captionText <- inlineListToLaTeX caption
let capt = if isEmpty captionText
then empty
- else text "\\addlinespace"
- $$ text "\\caption" <> braces captionText
+ else text "\\caption" <> braces captionText <> "\\\\"
rows' <- mapM (tableRowToLaTeX False aligns widths) rows
let colDescriptors = text $ concat $ map toColDescriptor aligns
modify $ \s -> s{ stTable = True }
return $ "\\begin{longtable}[c]" <>
braces ("@{}" <> colDescriptors <> "@{}")
-- the @{} removes extra space at beginning and end
+ $$ capt
$$ "\\toprule\\addlinespace"
$$ headers
$$ vcat rows'
$$ "\\bottomrule"
- $$ capt
$$ "\\end{longtable}"
toColDescriptor :: Alignment -> String
diff --git a/src/Text/Pandoc/Writers/Markdown.hs b/src/Text/Pandoc/Writers/Markdown.hs
index a67271a5d..78500d498 100644
--- a/src/Text/Pandoc/Writers/Markdown.hs
+++ b/src/Text/Pandoc/Writers/Markdown.hs
@@ -405,8 +405,8 @@ blockToMarkdown opts (CodeBlock attribs str) = return $
attrs = if isEnabled Ext_fenced_code_attributes opts
then nowrap $ " " <> attrsToMarkdown attribs
else case attribs of
- (_,[cls],_) -> " " <> text cls
- _ -> empty
+ (_,(cls:_),_) -> " " <> text cls
+ _ -> empty
blockToMarkdown opts (BlockQuote blocks) = do
st <- get
-- if we're writing literate haskell, put a space before the bird tracks
diff --git a/tests/Tests/Readers/Markdown.hs b/tests/Tests/Readers/Markdown.hs
index 709026d92..f7d07f6cd 100644
--- a/tests/Tests/Readers/Markdown.hs
+++ b/tests/Tests/Readers/Markdown.hs
@@ -149,6 +149,8 @@ tests = [ testGroup "inline code"
, "emph with spaced strong" =:
"*x **xx** x*"
=?> para (emph ("x" <> space <> strong "xx" <> space <> "x"))
+ , "intraword underscore with opening underscore (#1121)" =:
+ "_foot_ball_" =?> para (emph (text "foot_ball"))
]
, testGroup "raw LaTeX"
[ "in URL" =:
diff --git a/tests/tables.latex b/tests/tables.latex
index 1a87c4f71..eb665204d 100644
--- a/tests/tables.latex
+++ b/tests/tables.latex
@@ -1,6 +1,7 @@
Simple table with caption:
\begin{longtable}[c]{@{}rlcl@{}}
+\caption{Demonstration of simple table syntax.}\\
\toprule\addlinespace
Right & Left & Center & Default
\\\addlinespace
@@ -12,8 +13,6 @@ Right & Left & Center & Default
1 & 1 & 1 & 1
\\\addlinespace
\bottomrule
-\addlinespace
-\caption{Demonstration of simple table syntax.}
\end{longtable}
Simple table without caption:
@@ -35,6 +34,7 @@ Right & Left & Center & Default
Simple table indented two spaces:
\begin{longtable}[c]{@{}rlcl@{}}
+\caption{Demonstration of simple table syntax.}\\
\toprule\addlinespace
Right & Left & Center & Default
\\\addlinespace
@@ -46,13 +46,12 @@ Right & Left & Center & Default
1 & 1 & 1 & 1
\\\addlinespace
\bottomrule
-\addlinespace
-\caption{Demonstration of simple table syntax.}
\end{longtable}
Multiline table with caption:
\begin{longtable}[c]{@{}clrl@{}}
+\caption{Here's the caption. It may span multiple lines.}\\
\toprule\addlinespace
\begin{minipage}[b]{0.13\columnwidth}\centering
Centered Header
@@ -86,8 +85,6 @@ Here's another one. Note the blank line between rows.
\end{minipage}
\\\addlinespace
\bottomrule
-\addlinespace
-\caption{Here's the caption. It may span multiple lines.}
\end{longtable}
Multiline table without caption: