diff options
-rw-r--r-- | src/Text/Pandoc/Readers/Textile.hs | 30 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/DokuWiki.hs | 2 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/HTML.hs | 3 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/LaTeX.hs | 2 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/MediaWiki.hs | 2 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/OpenDocument.hs | 2 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/Texinfo.hs | 4 | ||||
-rw-r--r-- | tests/dokuwiki_inline_formatting.dokuwiki | 3 | ||||
-rw-r--r-- | tests/writer.dokuwiki | 3 | ||||
-rw-r--r-- | tests/writer.html | 3 | ||||
-rw-r--r-- | tests/writer.latex | 3 | ||||
-rw-r--r-- | tests/writer.mediawiki | 3 | ||||
-rw-r--r-- | tests/writer.opendocument | 3 | ||||
-rw-r--r-- | tests/writer.texinfo | 46 |
14 files changed, 67 insertions, 42 deletions
diff --git a/src/Text/Pandoc/Readers/Textile.hs b/src/Text/Pandoc/Readers/Textile.hs index ee64e8f2a..63ab80eb9 100644 --- a/src/Text/Pandoc/Readers/Textile.hs +++ b/src/Text/Pandoc/Readers/Textile.hs @@ -57,6 +57,7 @@ import qualified Text.Pandoc.Builder as B import Text.Pandoc.Options import Text.Pandoc.Parsing import Text.Pandoc.Readers.HTML ( htmlTag, isBlockTag ) +import Text.Pandoc.Shared (trim) import Text.Pandoc.Readers.LaTeX ( rawLaTeXInline, rawLaTeXBlock ) import Text.HTML.TagSoup (parseTags, innerText, fromAttrib, Tag(..)) import Text.HTML.TagSoup.Match @@ -325,33 +326,30 @@ para = B.para . trimInlines . mconcat <$> many1 inline -- Tables -- | A table cell spans until a pipe | -tableCell :: Parser [Char] ParserState Blocks -tableCell = do - c <- many1 (noneOf "|\n") - content <- trimInlines . mconcat <$> parseFromString (many1 inline) c +tableCell :: Bool -> Parser [Char] ParserState Blocks +tableCell headerCell = try $ do + char '|' + when headerCell $ () <$ string "_." + notFollowedBy blankline + raw <- trim <$> + many (noneOf "|\n" <|> try (char '\n' <* notFollowedBy blankline)) + content <- mconcat <$> parseFromString (many inline) raw return $ B.plain content -- | A table row is made of many table cells tableRow :: Parser [Char] ParserState [Blocks] -tableRow = try $ ( char '|' *> - (endBy1 tableCell (optional blankline *> char '|')) <* newline) - --- | Many table rows -tableRows :: Parser [Char] ParserState [[Blocks]] -tableRows = many1 tableRow +tableRow = many1 (tableCell False) <* char '|' <* newline --- | Table headers are made of cells separated by a tag "|_." -tableHeaders :: Parser [Char] ParserState [Blocks] -tableHeaders = let separator = (try $ string "|_.") in - try $ ( separator *> (sepBy1 tableCell separator) <* char '|' <* newline ) +tableHeader :: Parser [Char] ParserState [Blocks] +tableHeader = many1 (tableCell True) <* char '|' <* newline -- | A table with an optional header. Current implementation can -- handle tables with and without header, but will parse cells -- alignment attributes as content. table :: Parser [Char] ParserState Blocks table = try $ do - headers <- option mempty tableHeaders - rows <- tableRows + headers <- option mempty $ tableHeader + rows <- many1 tableRow blanklines let nbOfCols = max (length headers) (length $ head rows) return $ B.table mempty diff --git a/src/Text/Pandoc/Writers/DokuWiki.hs b/src/Text/Pandoc/Writers/DokuWiki.hs index eed45a965..17ff8a279 100644 --- a/src/Text/Pandoc/Writers/DokuWiki.hs +++ b/src/Text/Pandoc/Writers/DokuWiki.hs @@ -459,7 +459,7 @@ inlineToDokuWiki _ (RawInline f str) | f == Format "html" = return $ "<html>" ++ str ++ "</html>" | otherwise = return "" -inlineToDokuWiki _ (LineBreak) = return "\\\\ " +inlineToDokuWiki _ (LineBreak) = return "\\\\\n" inlineToDokuWiki _ Space = return " " diff --git a/src/Text/Pandoc/Writers/HTML.hs b/src/Text/Pandoc/Writers/HTML.hs index 1ae951e46..ef00ea036 100644 --- a/src/Text/Pandoc/Writers/HTML.hs +++ b/src/Text/Pandoc/Writers/HTML.hs @@ -656,7 +656,8 @@ inlineToHtml opts inline = case inline of (Str str) -> return $ strToHtml str (Space) -> return $ strToHtml " " - (LineBreak) -> return $ if writerHtml5 opts then H5.br else H.br + (LineBreak) -> return $ (if writerHtml5 opts then H5.br else H.br) + <> strToHtml "\n" (Span (id',classes,kvs) ils) -> inlineListToHtml opts ils >>= return . addAttrs opts attr' . H.span diff --git a/src/Text/Pandoc/Writers/LaTeX.hs b/src/Text/Pandoc/Writers/LaTeX.hs index d50ccb655..0e5ec5c18 100644 --- a/src/Text/Pandoc/Writers/LaTeX.hs +++ b/src/Text/Pandoc/Writers/LaTeX.hs @@ -802,7 +802,7 @@ inlineToLaTeX (RawInline f str) | f == Format "latex" || f == Format "tex" = return $ text str | otherwise = return empty -inlineToLaTeX (LineBreak) = return "\\\\" +inlineToLaTeX (LineBreak) = return $ "\\\\" <> cr inlineToLaTeX Space = return space inlineToLaTeX (Link txt ('#':ident, _)) = do contents <- inlineListToLaTeX txt diff --git a/src/Text/Pandoc/Writers/MediaWiki.hs b/src/Text/Pandoc/Writers/MediaWiki.hs index 4f03ee3bb..ccb39e295 100644 --- a/src/Text/Pandoc/Writers/MediaWiki.hs +++ b/src/Text/Pandoc/Writers/MediaWiki.hs @@ -375,7 +375,7 @@ inlineToMediaWiki (RawInline f str) | f == Format "html" = return str | otherwise = return "" -inlineToMediaWiki (LineBreak) = return "<br />" +inlineToMediaWiki (LineBreak) = return "<br />\n" inlineToMediaWiki Space = return " " diff --git a/src/Text/Pandoc/Writers/OpenDocument.hs b/src/Text/Pandoc/Writers/OpenDocument.hs index 901f827fb..865b7fb35 100644 --- a/src/Text/Pandoc/Writers/OpenDocument.hs +++ b/src/Text/Pandoc/Writers/OpenDocument.hs @@ -370,7 +370,7 @@ inlineToOpenDocument :: WriterOptions -> Inline -> State WriterState Doc inlineToOpenDocument o ils | Space <- ils = inTextStyle space | Span _ xs <- ils = inlinesToOpenDocument o xs - | LineBreak <- ils = return $ selfClosingTag "text:line-break" [] + | LineBreak <- ils = return $ selfClosingTag "text:line-break" [] <> cr | Str s <- ils = inTextStyle $ handleSpaces $ escapeStringForXML s | Emph l <- ils = withTextStyle Italic $ inlinesToOpenDocument o l | Strong l <- ils = withTextStyle Bold $ inlinesToOpenDocument o l diff --git a/src/Text/Pandoc/Writers/Texinfo.hs b/src/Text/Pandoc/Writers/Texinfo.hs index 8fd177fd3..792718e95 100644 --- a/src/Text/Pandoc/Writers/Texinfo.hs +++ b/src/Text/Pandoc/Writers/Texinfo.hs @@ -421,8 +421,8 @@ inlineToTexinfo (RawInline f str) return $ text "@tex" $$ text str $$ text "@end tex" | f == "texinfo" = return $ text str | otherwise = return empty -inlineToTexinfo (LineBreak) = return $ text "@*" -inlineToTexinfo Space = return $ char ' ' +inlineToTexinfo (LineBreak) = return $ text "@*" <> cr +inlineToTexinfo Space = return space inlineToTexinfo (Link txt (src@('#':_), _)) = do contents <- escapeCommas $ inlineListToTexinfo txt diff --git a/tests/dokuwiki_inline_formatting.dokuwiki b/tests/dokuwiki_inline_formatting.dokuwiki index dd5cb52b4..262094184 100644 --- a/tests/dokuwiki_inline_formatting.dokuwiki +++ b/tests/dokuwiki_inline_formatting.dokuwiki @@ -6,7 +6,8 @@ Some people use single underlines for //emphasis//. Above the line is <sup>superscript</sup> and below the line is <sub>subscript</sub>. -A line\\ break. +A line\\ +break. hello %%//%% world %%**%% from %%__%% me diff --git a/tests/writer.dokuwiki b/tests/writer.dokuwiki index dc14e9b00..2c3c9b1b5 100644 --- a/tests/writer.dokuwiki +++ b/tests/writer.dokuwiki @@ -36,7 +36,8 @@ In Markdown 1.0.0 and earlier. Version 8. This line turns into a list item. Beca Here’s one with a bullet. * criminey. -There should be a hard line break\\ here. +There should be a hard line break\\ +here. ---- diff --git a/tests/writer.html b/tests/writer.html index 6f7d1764b..1357fa7c4 100644 --- a/tests/writer.html +++ b/tests/writer.html @@ -35,7 +35,8 @@ <p>Here’s a regular paragraph.</p> <p>In Markdown 1.0.0 and earlier. Version 8. This line turns into a list item. Because a hard-wrapped line in the middle of a paragraph looked like a list item.</p> <p>Here’s one with a bullet. * criminey.</p> -<p>There should be a hard line break<br />here.</p> +<p>There should be a hard line break<br /> +here.</p> <hr /> <h1 id="block-quotes">Block Quotes</h1> <p>E-mail style:</p> diff --git a/tests/writer.latex b/tests/writer.latex index 5b41bac75..f7123be98 100644 --- a/tests/writer.latex +++ b/tests/writer.latex @@ -109,7 +109,8 @@ item. Here's one with a bullet. * criminey. -There should be a hard line break\\here. +There should be a hard line break\\ +here. \begin{center}\rule{0.5\linewidth}{\linethickness}\end{center} diff --git a/tests/writer.mediawiki b/tests/writer.mediawiki index efd43cb04..b8b99c5e7 100644 --- a/tests/writer.mediawiki +++ b/tests/writer.mediawiki @@ -36,7 +36,8 @@ In Markdown 1.0.0 and earlier. Version 8. This line turns into a list item. Beca Here’s one with a bullet. * criminey. -There should be a hard line break<br />here. +There should be a hard line break<br /> +here. ----- diff --git a/tests/writer.opendocument b/tests/writer.opendocument index 81c793a62..ac436150d 100644 --- a/tests/writer.opendocument +++ b/tests/writer.opendocument @@ -896,7 +896,8 @@ of a paragraph looked like a list item.</text:p> <text:p text:style-name="Text_20_body">Here’s one with a bullet. * criminey.</text:p> <text:p text:style-name="Text_20_body">There should be a hard line -break<text:line-break />here.</text:p> +break<text:line-break /> +here.</text:p> <text:p text:style-name="Horizontal_20_Line" /> <text:h text:style-name="Heading_20_1" text:outline-level="1">Block Quotes</text:h> diff --git a/tests/writer.texinfo b/tests/writer.texinfo index 7b59ea651..ca87da1a9 100644 --- a/tests/writer.texinfo +++ b/tests/writer.texinfo @@ -36,7 +36,8 @@ July 17, 2006 @node Top @top Pandoc Test Suite -This is a set of tests for pandoc. Most of them are adapted from John Gruber's markdown test suite. +This is a set of tests for pandoc. Most of them are adapted from John Gruber's +markdown test suite. @iftex @bigskip@hrule@bigskip @@ -125,11 +126,14 @@ with no blank line @anchor{#paragraphs} Here's a regular paragraph. -In Markdown 1.0.0 and earlier. Version 8. This line turns into a list item. Because a hard-wrapped line in the middle of a paragraph looked like a list item. +In Markdown 1.0.0 and earlier. Version 8. This line turns into a list item. +Because a hard-wrapped line in the middle of a paragraph looked like a list +item. Here's one with a bullet. * criminey. -There should be a hard line break@*here. +There should be a hard line break@* +here. @iftex @bigskip@hrule@bigskip @@ -734,11 +738,14 @@ This is code: @code{>}, @code{$}, @code{\}, @code{\$}, @code{<html>}. @textstrikeout{This is @emph{strikeout}.} -Superscripts: a@textsuperscript{bc}d a@textsuperscript{@emph{hello}} a@textsuperscript{hello@ there}. +Superscripts: a@textsuperscript{bc}d a@textsuperscript{@emph{hello}} +a@textsuperscript{hello@ there}. -Subscripts: H@textsubscript{2}O, H@textsubscript{23}O, H@textsubscript{many@ of@ them}O. +Subscripts: H@textsubscript{2}O, H@textsubscript{23}O, +H@textsubscript{many@ of@ them}O. -These should not be superscripts or subscripts, because of the unescaped spaces: a^b c^d, a~b c~d. +These should not be superscripts or subscripts, because of the unescaped +spaces: a^b c^d, a~b c~d. @iftex @bigskip@hrule@bigskip @@ -758,7 +765,8 @@ These should not be superscripts or subscripts, because of the unescaped spaces: `He said, ``I want to go.''' Were you alive in the 70's? -Here is some quoted `@code{code}' and a ``@uref{http://example.com/?foo=1&bar=2,quoted link}''. +Here is some quoted `@code{code}' and a +``@uref{http://example.com/?foo=1&bar=2,quoted link}''. Some dashes: one---two --- three---four --- five. @@ -792,7 +800,8 @@ Ellipses@dots{}and@dots{}and@dots{}. @item @math{p}-Tree @item -Here's some display math: @math{\frac{d}{dx}f(x)=\lim_{h\to 0}\frac{f(x+h)-f(x)}{h}} +Here's some display math: +@math{\frac{d}{dx}f(x)=\lim_{h\to 0}\frac{f(x+h)-f(x)}{h}} @item Here's one that has a line break in it: @math{\alpha + \omega \times x^2}. @end itemize @@ -803,7 +812,8 @@ These shouldn't be math: @item To get the famous equation, write @code{$e = mc^2$}. @item -$22,000 is a @emph{lot} of money. So is $34,000. (It worked if ``lot'' is emphasized.) +$22,000 is a @emph{lot} of money. So is $34,000. (It worked if ``lot'' is +emphasized.) @item Shoes ($20) and socks ($5). @item @@ -956,7 +966,8 @@ Foo @uref{/url/,biz}. @node With ampersands @section With ampersands @anchor{#with-ampersands} -Here's a @uref{http://example.com/?foo=1&bar=2,link with an ampersand in the URL}. +Here's a @uref{http://example.com/?foo=1&bar=2,link with an ampersand in the +URL}. Here's a link with an amersand in the link text: @uref{http://att.com/,AT&T}. @@ -1018,15 +1029,24 @@ Here is a movie @image{movie,,,movie,jpg} icon. @node Footnotes @chapter Footnotes @anchor{#footnotes} -Here is a footnote reference,@footnote{Here is the footnote. It can go anywhere after the footnote reference. It need not be placed at the end of the document.} and another.@footnote{Here's the long note. This one contains multiple blocks. +Here is a footnote reference,@footnote{Here is the footnote. It can go +anywhere after the footnote reference. It need not be placed at the end of the +document.} and another.@footnote{Here's the long note. This one contains +multiple blocks. -Subsequent blocks are indented to show that they belong to the footnote (as with list items). +Subsequent blocks are indented to show that they belong to the footnote (as +with list items). @verbatim { <code> } @end verbatim -If you want, you can indent every line, but you can also be lazy and just indent the first line of each block.} This should @emph{not} be a footnote reference, because it contains a space.[^my note] Here is an inline note.@footnote{This is @emph{easier} to type. Inline notes may contain @uref{http://google.com,links} and @code{]} verbatim characters, as well as [bracketed text].} +If you want, you can indent every line, but you can also be lazy and just +indent the first line of each block.} This should @emph{not} be a footnote +reference, because it contains a space.[^my note] Here is an inline +note.@footnote{This is @emph{easier} to type. Inline notes may contain +@uref{http://google.com,links} and @code{]} verbatim characters, as well as +[bracketed text].} @quotation Notes can go in quotes.@footnote{In quote.} |