diff options
Diffstat (limited to 'src')
-rw-r--r-- | src/Text/Pandoc/Options.hs | 6 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/Markdown.hs | 12 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/HTML.hs | 2 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/Markdown.hs | 36 | ||||
-rw-r--r-- | src/pandoc.hs | 5 |
5 files changed, 36 insertions, 25 deletions
diff --git a/src/Text/Pandoc/Options.hs b/src/Text/Pandoc/Options.hs index ef4f18633..efcb0ea52 100644 --- a/src/Text/Pandoc/Options.hs +++ b/src/Text/Pandoc/Options.hs @@ -56,7 +56,9 @@ data Extension = Ext_footnotes | Ext_tex_math | Ext_latex_macros | Ext_delimited_code_blocks + | Ext_inline_code_attributes | Ext_markdown_in_html_blocks + | Ext_escaped_line_breaks | Ext_autolink_code_spans | Ext_fancy_lists | Ext_startnum @@ -154,7 +156,7 @@ data WriterOptions = WriterOptions , writerIgnoreNotes :: Bool -- ^ Ignore footnotes (used in making toc) , writerNumberSections :: Bool -- ^ Number sections in LaTeX , writerSectionDivs :: Bool -- ^ Put sections in div tags in HTML - , writerStrictMarkdown :: Bool -- ^ Use strict markdown syntax + , writerExtensions :: Set Extension -- ^ Markdown extensions that can be used , writerReferenceLinks :: Bool -- ^ Use reference links in writing markdown, rst , writerWrapText :: Bool -- ^ Wrap text to line length , writerColumns :: Int -- ^ Characters in a line (for text wrapping) @@ -194,7 +196,7 @@ instance Default WriterOptions where , writerIgnoreNotes = False , writerNumberSections = False , writerSectionDivs = False - , writerStrictMarkdown = False + , writerExtensions = Set.fromList [minBound..maxBound] , writerReferenceLinks = False , writerWrapText = True , writerColumns = 72 diff --git a/src/Text/Pandoc/Readers/Markdown.hs b/src/Text/Pandoc/Readers/Markdown.hs index ae51fdd5a..8b34b9b4a 100644 --- a/src/Text/Pandoc/Readers/Markdown.hs +++ b/src/Text/Pandoc/Readers/Markdown.hs @@ -1005,10 +1005,11 @@ escapedChar' = try $ do escapedChar :: Parser [Char] ParserState Inline escapedChar = do result <- escapedChar' - return $ case result of - ' ' -> Str "\160" -- "\ " is a nonbreaking space - '\n' -> LineBreak -- "\[newline]" is a linebreak - _ -> Str [result] + case result of + ' ' -> return $ Str "\160" -- "\ " is a nonbreaking space + '\n' -> guardEnabled Ext_escaped_line_breaks >> + return LineBreak -- "\[newline]" is a linebreak + _ -> return $ Str [result] ltSign :: Parser [Char] ParserState Inline ltSign = do @@ -1042,7 +1043,8 @@ code = try $ do (char '\n' >> notFollowedBy' blankline >> return " ")) (try (skipSpaces >> count (length starts) (char '`') >> notFollowedBy (char '`'))) - attr <- option ([],[],[]) (try $ optional whitespace >> attributes) + attr <- option ([],[],[]) (try $ guardEnabled Ext_inline_code_attributes >> + optional whitespace >> attributes) return $ Code attr $ removeLeadingTrailingSpace $ concat result mathWord :: Parser [Char] st [Char] diff --git a/src/Text/Pandoc/Writers/HTML.hs b/src/Text/Pandoc/Writers/HTML.hs index a5f85921c..78361dafc 100644 --- a/src/Text/Pandoc/Writers/HTML.hs +++ b/src/Text/Pandoc/Writers/HTML.hs @@ -273,7 +273,7 @@ elementToHtml slideLevel opts (Sec level num id' title' elements) = do -- title slides have no content of their own then filter isSec elements else elements - let header'' = if (writerStrictMarkdown opts || writerSectionDivs opts || + let header'' = if (writerSectionDivs opts || writerSlideVariant opts == S5Slides || slide) then header' else header' ! prefixedId opts id' diff --git a/src/Text/Pandoc/Writers/Markdown.hs b/src/Text/Pandoc/Writers/Markdown.hs index 3a0f586db..dac9bb8cc 100644 --- a/src/Text/Pandoc/Writers/Markdown.hs +++ b/src/Text/Pandoc/Writers/Markdown.hs @@ -40,6 +40,7 @@ import Text.Pandoc.Parsing hiding (blankline, char, space) import Data.List ( group, isPrefixOf, find, intersperse, transpose ) import Text.Pandoc.Pretty import Control.Monad.State +import qualified Data.Set as Set type Notes = [[Block]] type Refs = [([Inline], Target)] @@ -47,6 +48,9 @@ data WriterState = WriterState { stNotes :: Notes , stRefs :: Refs , stPlain :: Bool } +isEnabled :: Extension -> WriterOptions -> Bool +isEnabled ext opts = ext `Set.member` (writerExtensions opts) + -- | Convert Pandoc to Markdown. writeMarkdown :: WriterOptions -> Pandoc -> String writeMarkdown opts document = @@ -58,7 +62,7 @@ writeMarkdown opts document = -- pictures, or inline formatting). writePlain :: WriterOptions -> Pandoc -> String writePlain opts document = - evalState (pandocToMarkdown opts{writerStrictMarkdown = True} + evalState (pandocToMarkdown opts{writerExtensions = Set.empty} document') WriterState{ stNotes = [] , stRefs = [] , stPlain = True } @@ -215,7 +219,7 @@ blockToMarkdown opts (Para inlines) = do contents <- inlineListToMarkdown opts inlines -- escape if para starts with ordered list marker st <- get - let esc = if (not (writerStrictMarkdown opts)) && + let esc = if isEnabled Ext_all_symbols_escapable opts && not (stPlain st) && beginsWithOrderedListMarker (render Nothing contents) then text "\x200B" -- zero-width space, a hack @@ -251,13 +255,13 @@ blockToMarkdown opts (CodeBlock (_,classes,_) str) writerLiterateHaskell opts = return $ prefixed "> " (text str) <> blankline blockToMarkdown opts (CodeBlock attribs str) = return $ - if writerStrictMarkdown opts || attribs == nullAttr - then nest (writerTabStop opts) (text str) <> blankline - else -- use delimited code block + if isEnabled Ext_delimited_code_blocks opts && attribs /= nullAttr + then -- use delimited code block (tildes <> space <> attrs <> cr <> text str <> cr <> tildes) <> blankline - where tildes = text "~~~~" - attrs = attrsToMarkdown attribs + else nest (writerTabStop opts) (text str) <> blankline + where tildes = text "~~~~" + attrs = attrsToMarkdown attribs blockToMarkdown opts (BlockQuote blocks) = do st <- get -- if we're writing literate haskell, put a space before the bird tracks @@ -372,9 +376,10 @@ blockListToMarkdown opts blocks = -- insert comment between list and indented code block, or the -- code block will be treated as a list continuation paragraph where fixBlocks (b : CodeBlock attr x : rest) - | (writerStrictMarkdown opts || attr == nullAttr) && isListBlock b = + | (not (isEnabled Ext_delimited_code_blocks opts) || attr == nullAttr) + && isListBlock b = b : RawBlock "html" "<!-- -->\n" : CodeBlock attr x : - fixBlocks rest + fixBlocks rest fixBlocks (x : xs) = x : fixBlocks xs fixBlocks [] = [] isListBlock (BulletList _) = True @@ -443,9 +448,9 @@ inlineToMarkdown opts (Code attr str) = else maximum $ map length tickGroups marker = replicate (longest + 1) '`' spacer = if (longest == 0) then "" else " " - attrs = if writerStrictMarkdown opts || attr == nullAttr - then empty - else attrsToMarkdown attr + attrs = if isEnabled Ext_inline_code_attributes opts && attr /= nullAttr + then attrsToMarkdown attr + else empty in return $ text (marker ++ spacer ++ str ++ spacer ++ marker) <> attrs inlineToMarkdown _ (Str str) = do st <- get @@ -460,10 +465,9 @@ inlineToMarkdown _ (RawInline f str) | f == "html" || f == "latex" || f == "tex" || f == "markdown" = return $ text str inlineToMarkdown _ (RawInline _ _) = return empty -inlineToMarkdown opts (LineBreak) = return $ - if writerStrictMarkdown opts - then " " <> cr - else "\\" <> cr +inlineToMarkdown opts (LineBreak) + | isEnabled Ext_escaped_line_breaks opts = return $ "\\" <> cr + | otherwise = return $ " " <> cr inlineToMarkdown _ Space = return space inlineToMarkdown opts (Cite (c:cs) lst) | writerCiteMethod opts == Citeproc = inlineListToMarkdown opts lst diff --git a/src/pandoc.hs b/src/pandoc.hs index 2a7950fe7..d60f9ec12 100644 --- a/src/pandoc.hs +++ b/src/pandoc.hs @@ -969,7 +969,10 @@ main = do writerIgnoreNotes = False, writerNumberSections = numberSections, writerSectionDivs = sectionDivs, - writerStrictMarkdown = strict, + writerExtensions = if strict + then Set.empty + else Set.fromList + [minBound..maxBound], writerReferenceLinks = referenceLinks, writerWrapText = wrap, writerColumns = columns, |