diff options
author | Aner Lucero <4rgento@gmail.com> | 2020-11-14 20:09:44 -0300 |
---|---|---|
committer | John MacFarlane <jgm@berkeley.edu> | 2020-11-14 21:33:32 -0800 |
commit | f63b76e1698b0d7eba6b43ef45faaeee2b01b9ca (patch) | |
tree | 58e6458690ab189e00c15b98ccb88e440c97e396 /src/Text/Pandoc | |
parent | b8d17f7ae8ed37784adcfaa4f89d0d28f52fffff (diff) | |
download | pandoc-f63b76e1698b0d7eba6b43ef45faaeee2b01b9ca.tar.gz |
Markdown writer: default to using ATX headings.
Previously we used Setext (underlined) headings by default.
The default is now ATX (`##` style).
* Add the `--markdown-headings=atx|setext` option.
* Deprecate `--atx-headers`.
* Add constructor 'ATXHeadingInLHS` constructor to `LogMessage` [API change].
* Support `markdown-headings` in defaults files.
* Document new options in MANUAL.
Closes #6662.
Diffstat (limited to 'src/Text/Pandoc')
-rw-r--r-- | src/Text/Pandoc/App/CommandLineOptions.hs | 19 | ||||
-rw-r--r-- | src/Text/Pandoc/App/Opt.hs | 8 | ||||
-rw-r--r-- | src/Text/Pandoc/Logging.hs | 85 | ||||
-rw-r--r-- | src/Text/Pandoc/Options.hs | 2 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/Markdown.hs | 7 |
5 files changed, 81 insertions, 40 deletions
diff --git a/src/Text/Pandoc/App/CommandLineOptions.hs b/src/Text/Pandoc/App/CommandLineOptions.hs index a82d8380e..661c6e06d 100644 --- a/src/Text/Pandoc/App/CommandLineOptions.hs +++ b/src/Text/Pandoc/App/CommandLineOptions.hs @@ -529,9 +529,26 @@ options = , Option "" ["atx-headers"] (NoArg - (\opt -> return opt { optSetextHeaders = False } )) + (\opt -> do + deprecatedOption "--atx-headers" + "use --markdown-headings=atx" + return opt { optSetextHeaders = False } )) "" -- "Use atx-style headers for markdown" + , Option "" ["markdown-headings"] + (ReqArg + (\arg opt -> do + headingFormat <- case arg of + "setext" -> pure True + "atx" -> pure False + _ -> E.throwIO $ PandocOptionError $ T.pack + ("Unknown markdown heading format: " ++ arg ++ + ". Expecting atx or setext") + pure opt { optSetextHeaders = headingFormat } + ) + "setext|atx") + "" + , Option "" ["listings"] (NoArg (\opt -> return opt { optListings = True })) diff --git a/src/Text/Pandoc/App/Opt.hs b/src/Text/Pandoc/App/Opt.hs index 64c61fb74..7e15b2cb0 100644 --- a/src/Text/Pandoc/App/Opt.hs +++ b/src/Text/Pandoc/App/Opt.hs @@ -330,6 +330,12 @@ doOpt (k',v) = do parseYAML v >>= \x -> return (\o -> o{ optSlideLevel = x }) "atx-headers" -> parseYAML v >>= \x -> return (\o -> o{ optSetextHeaders = not x }) + "markdown-headings" -> + parseYAML v >>= \x -> return (\o -> + case (T.toLower x) of + "atx" -> o{ optSetextHeaders = False } + "setext" -> o{ optSetextHeaders = True } + _ -> o) "ascii" -> parseYAML v >>= \x -> return (\o -> o{ optAscii = x }) "default-image-extension" -> @@ -469,7 +475,7 @@ defaultOpts = Opt , optPdfEngine = Nothing , optPdfEngineOpts = [] , optSlideLevel = Nothing - , optSetextHeaders = True + , optSetextHeaders = False , optAscii = False , optDefaultImageExtension = "" , optExtractMedia = Nothing diff --git a/src/Text/Pandoc/Logging.hs b/src/Text/Pandoc/Logging.hs index 5c9330b7b..825fdaadb 100644 --- a/src/Text/Pandoc/Logging.hs +++ b/src/Text/Pandoc/Logging.hs @@ -31,6 +31,7 @@ import Data.Aeson.Encode.Pretty (Config (..), defConfig, encodePretty', import qualified Data.ByteString.Lazy as BL import Data.Data (Data, toConstr) import qualified Data.Text as Text +import Data.Text (Text) import Data.Typeable (Typeable) import GHC.Generics (Generic) import Text.Pandoc.Definition @@ -59,45 +60,46 @@ instance FromYAML Verbosity where _ -> mzero data LogMessage = - SkippedContent Text.Text SourcePos - | IgnoredElement Text.Text - | DuplicateLinkReference Text.Text SourcePos - | DuplicateNoteReference Text.Text SourcePos - | NoteDefinedButNotUsed Text.Text SourcePos - | DuplicateIdentifier Text.Text SourcePos - | ReferenceNotFound Text.Text SourcePos - | CircularReference Text.Text SourcePos - | UndefinedToggle Text.Text SourcePos - | ParsingUnescaped Text.Text SourcePos - | CouldNotLoadIncludeFile Text.Text SourcePos - | MacroAlreadyDefined Text.Text SourcePos + SkippedContent Text SourcePos + | IgnoredElement Text + | DuplicateLinkReference Text SourcePos + | DuplicateNoteReference Text SourcePos + | NoteDefinedButNotUsed Text SourcePos + | DuplicateIdentifier Text SourcePos + | ReferenceNotFound Text SourcePos + | CircularReference Text SourcePos + | UndefinedToggle Text SourcePos + | ParsingUnescaped Text SourcePos + | CouldNotLoadIncludeFile Text SourcePos + | MacroAlreadyDefined Text SourcePos | InlineNotRendered Inline | BlockNotRendered Block - | DocxParserWarning Text.Text - | IgnoredIOError Text.Text - | CouldNotFetchResource Text.Text Text.Text - | CouldNotDetermineImageSize Text.Text Text.Text - | CouldNotConvertImage Text.Text Text.Text - | CouldNotDetermineMimeType Text.Text - | CouldNotConvertTeXMath Text.Text Text.Text - | CouldNotParseCSS Text.Text - | Fetching Text.Text - | Extracting Text.Text - | NoTitleElement Text.Text + | DocxParserWarning Text + | IgnoredIOError Text + | CouldNotFetchResource Text Text + | CouldNotDetermineImageSize Text Text + | CouldNotConvertImage Text Text + | CouldNotDetermineMimeType Text + | CouldNotConvertTeXMath Text Text + | CouldNotParseCSS Text + | Fetching Text + | Extracting Text + | NoTitleElement Text | NoLangSpecified - | InvalidLang Text.Text - | CouldNotHighlight Text.Text - | MissingCharacter Text.Text - | Deprecated Text.Text Text.Text - | NoTranslation Text.Text - | CouldNotLoadTranslations Text.Text Text.Text - | UnusualConversion Text.Text - | UnexpectedXmlElement Text.Text Text.Text - | UnknownOrgExportOption Text.Text - | CouldNotDeduceFormat [Text.Text] Text.Text + | InvalidLang Text + | CouldNotHighlight Text + | MissingCharacter Text + | Deprecated Text Text + | NoTranslation Text + | CouldNotLoadTranslations Text Text + | UnusualConversion Text + | UnexpectedXmlElement Text Text + | UnknownOrgExportOption Text + | CouldNotDeduceFormat [Text] Text | RunningFilter FilePath | FilterCompleted FilePath Integer - | CiteprocWarning Text.Text + | CiteprocWarning Text + | ATXHeadingInLHS Int Text deriving (Show, Eq, Data, Ord, Typeable, Generic) instance ToJSON LogMessage where @@ -224,8 +226,11 @@ instance ToJSON LogMessage where ,"milliseconds" .= Text.pack (show ms) ] CiteprocWarning msg -> ["message" .= msg] + ATXHeadingInLHS lvl contents -> + ["level" .= lvl + ,"contents" .= contents] -showPos :: SourcePos -> Text.Text +showPos :: SourcePos -> Text showPos pos = Text.pack $ sn ++ "line " ++ show (sourceLine pos) ++ " column " ++ show (sourceColumn pos) where sn = if sourceName pos == "source" || sourceName pos == "" @@ -238,7 +243,7 @@ encodeLogMessages ms = keyOrder [ "type", "verbosity", "contents", "message", "path", "source", "line", "column" ] } ms -showLogMessage :: LogMessage -> Text.Text +showLogMessage :: LogMessage -> Text showLogMessage msg = case msg of SkippedContent s pos -> @@ -333,6 +338,13 @@ showLogMessage msg = FilterCompleted fp ms -> "Completed filter " <> Text.pack fp <> " in " <> Text.pack (show ms) <> " ms" CiteprocWarning ms -> "Citeproc: " <> ms + ATXHeadingInLHS lvl contents -> + "Rendering heading '" <> contents <> "' as a paragraph.\n" <> + "ATX headings cannot be used in literate Haskell, because " <> + "'#' is not\nallowed in column 1." <> + if lvl < 3 + then " Consider using --markdown-headings=setext." + else "" messageVerbosity :: LogMessage -> Verbosity messageVerbosity msg = @@ -378,3 +390,4 @@ messageVerbosity msg = RunningFilter{} -> INFO FilterCompleted{} -> INFO CiteprocWarning{} -> WARNING + ATXHeadingInLHS{} -> WARNING diff --git a/src/Text/Pandoc/Options.hs b/src/Text/Pandoc/Options.hs index f1d9d44b7..c7f1a56fa 100644 --- a/src/Text/Pandoc/Options.hs +++ b/src/Text/Pandoc/Options.hs @@ -289,7 +289,7 @@ instance Default WriterOptions where , writerTopLevelDivision = TopLevelDefault , writerListings = False , writerHighlightStyle = Just pygments - , writerSetextHeaders = True + , writerSetextHeaders = False , writerEpubSubdirectory = "EPUB" , writerEpubMetadata = Nothing , writerEpubFonts = [] diff --git a/src/Text/Pandoc/Writers/Markdown.hs b/src/Text/Pandoc/Writers/Markdown.hs index 0aca83ad0..6aec6b244 100644 --- a/src/Text/Pandoc/Writers/Markdown.hs +++ b/src/Text/Pandoc/Writers/Markdown.hs @@ -514,6 +514,7 @@ blockToMarkdown' opts b@(RawBlock f str) = do blockToMarkdown' opts HorizontalRule = return $ blankline <> literal (T.replicate (writerColumns opts) "-") <> blankline blockToMarkdown' opts (Header level attr inlines) = do + -- first, if we're putting references at the end of a section, we -- put them here. blkLevel <- asks envBlockLevel @@ -543,8 +544,12 @@ blockToMarkdown' opts (Header level attr inlines) = do isEnabled Ext_gutenberg opts then capitalize inlines else inlines + let setext = writerSetextHeaders opts - hdr = nowrap $ case level of + when (not setext && isEnabled Ext_literate_haskell opts) $ + report $ ATXHeadingInLHS level (render Nothing contents) + + let hdr = nowrap $ case level of 1 | variant == PlainText -> if isEnabled Ext_gutenberg opts then blanklines 3 <> contents <> blanklines 2 |