From 0198e9507190e5b7d4000605641694aa570f3c10 Mon Sep 17 00:00:00 2001
From: Kristof Bastiaensen <kristof@vleeuwen.org>
Date: Tue, 14 Oct 2014 13:28:28 +0200
Subject: [PATCH] Use '=' instead of '#' for atx-style headers in markdown+lhs.

---
 README                              |  3 ++-
 src/Text/Pandoc/Readers/Markdown.hs | 12 +++++++++---
 2 files changed, 11 insertions(+), 4 deletions(-)

diff --git a/README b/README
index 556c35bc8..d2fcd51f1 100644
--- a/README
+++ b/README
@@ -3080,7 +3080,8 @@ literate Haskell source. This means that
 
   - In markdown input, "bird track" sections will be parsed as Haskell
     code rather than block quotations.  Text between `\begin{code}`
-    and `\end{code}` will also be treated as Haskell code.
+    and `\end{code}` will also be treated as Haskell code.  For
+    atx-style headers the character '=' will be used instead of '#'.
 
   - In markdown output, code blocks with classes `haskell` and `literate`
     will be rendered using bird tracks, and block quotations will be
diff --git a/src/Text/Pandoc/Readers/Markdown.hs b/src/Text/Pandoc/Readers/Markdown.hs
index 02a787670..25a303f52 100644
--- a/src/Text/Pandoc/Readers/Markdown.hs
+++ b/src/Text/Pandoc/Readers/Markdown.hs
@@ -487,9 +487,15 @@ block = do
 header :: MarkdownParser (F Blocks)
 header = setextHeader <|> atxHeader <?> "header"
 
+atxChar :: MarkdownParser Char
+atxChar = do
+  exts <- getOption readerExtensions
+  return $ if Set.member Ext_literate_haskell exts
+    then '=' else '#'
+
 atxHeader :: MarkdownParser (F Blocks)
 atxHeader = try $ do
-  level <- many1 (char '#') >>= return . length
+  level <- atxChar >>= many1 . char >>= return . length
   notFollowedBy $ guardEnabled Ext_fancy_lists >>
                   (char '.' <|> char ')') -- this would be a list
   skipSpaces
@@ -502,7 +508,7 @@ atxClosing :: MarkdownParser Attr
 atxClosing = try $ do
   attr' <- option nullAttr
              (guardEnabled Ext_mmd_header_identifiers >> mmdHeaderIdentifier)
-  skipMany (char '#')
+  skipMany . char =<< atxChar
   skipSpaces
   attr <- option attr'
              (guardEnabled Ext_header_attributes >> attributes)
@@ -1614,7 +1620,7 @@ endline = try $ do
   when (stateParserContext st == ListItemState) $ notFollowedBy listStart
   guardDisabled Ext_lists_without_preceding_blankline <|> notFollowedBy listStart
   guardEnabled Ext_blank_before_blockquote <|> notFollowedBy emailBlockQuoteStart
-  guardEnabled Ext_blank_before_header <|> notFollowedBy (char '#') -- atx header
+  guardEnabled Ext_blank_before_header <|> (notFollowedBy . char =<< atxChar) -- atx header
   guardDisabled Ext_backtick_code_blocks <|>
      notFollowedBy (() <$ (lookAhead (char '`') >> codeBlockFenced))
   notFollowedByHtmlCloser