aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc
diff options
context:
space:
mode:
authorKonstantin Zudov <konstantin@anche.no>2015-03-03 03:28:56 +0200
committerKonstantin Zudov <konstantin@anche.no>2015-03-10 20:32:24 +0200
commitb9f77ed03d0e4a0651d7508d563e880556690fcf (patch)
tree41f95866036702b3c78289bab0b83f6089ca2524 /src/Text/Pandoc
parent4f0c5c30809f09bd700cd47035f86a3db1c64669 (diff)
downloadpandoc-b9f77ed03d0e4a0651d7508d563e880556690fcf.tar.gz
Support shortcut reference links in markdown writer
Issue #1977 Most markdown processors support the [shortcut format] for reference links. Pandoc's markdown reader parsed this shortcuts unoptionally. Pandoc's markdown writer (with --reference-links option) never shortcutted links. This commit adds an extension `shortcut_reference_links`. The extension is enabled by default for those markdown flavors that support reading shortcut reference links, namely: - pandoc - strict pandoc - github flavoured - PHPmarkdown If extension is enabled, reader parses the shortcuts in the same way as it preveously did. Otherwise it would parse them as normal text. If extension is enabled, writer outputs shortcut reference links unless doing so would cause problems (see test cases in `tests/Tests/Writers/Markdown.hs`).
Diffstat (limited to 'src/Text/Pandoc')
-rw-r--r--src/Text/Pandoc/Options.hs8
-rw-r--r--src/Text/Pandoc/Readers/Markdown.hs1
-rw-r--r--src/Text/Pandoc/Writers/Markdown.hs84
3 files changed, 63 insertions, 30 deletions
diff --git a/src/Text/Pandoc/Options.hs b/src/Text/Pandoc/Options.hs
index 24e31fbb6..48803d36f 100644
--- a/src/Text/Pandoc/Options.hs
+++ b/src/Text/Pandoc/Options.hs
@@ -109,6 +109,7 @@ data Extension =
| Ext_implicit_header_references -- ^ Implicit reference links for headers
| Ext_line_blocks -- ^ RST style line blocks
| Ext_epub_html_exts -- ^ Recognise the EPUB extended version of HTML
+ | Ext_shortcut_reference_links -- ^ Shortcut reference links
deriving (Show, Read, Enum, Eq, Ord, Bounded)
pandocExtensions :: Set Extension
@@ -151,6 +152,7 @@ pandocExtensions = Set.fromList
, Ext_header_attributes
, Ext_implicit_header_references
, Ext_line_blocks
+ , Ext_shortcut_reference_links
]
phpMarkdownExtraExtensions :: Set Extension
@@ -164,6 +166,7 @@ phpMarkdownExtraExtensions = Set.fromList
, Ext_intraword_underscores
, Ext_header_attributes
, Ext_abbreviations
+ , Ext_shortcut_reference_links
]
githubMarkdownExtensions :: Set Extension
@@ -180,6 +183,7 @@ githubMarkdownExtensions = Set.fromList
, Ext_strikeout
, Ext_hard_line_breaks
, Ext_lists_without_preceding_blankline
+ , Ext_shortcut_reference_links
]
multimarkdownExtensions :: Set Extension
@@ -202,7 +206,9 @@ multimarkdownExtensions = Set.fromList
strictExtensions :: Set Extension
strictExtensions = Set.fromList
- [ Ext_raw_html ]
+ [ Ext_raw_html
+ , Ext_shortcut_reference_links
+ ]
data ReaderOptions = ReaderOptions{
readerExtensions :: Set Extension -- ^ Syntax extensions
diff --git a/src/Text/Pandoc/Readers/Markdown.hs b/src/Text/Pandoc/Readers/Markdown.hs
index 910936b34..9e6ad0e13 100644
--- a/src/Text/Pandoc/Readers/Markdown.hs
+++ b/src/Text/Pandoc/Readers/Markdown.hs
@@ -1679,6 +1679,7 @@ referenceLink constructor (lab, raw) = do
lookAhead (try (spnl >> normalCite >> return (mempty, "")))
<|>
try (spnl >> reference)
+ when (raw' == "") $ guardEnabled Ext_shortcut_reference_links
let labIsRef = raw' == "" || raw' == "[]"
let key = toKey $ if labIsRef then raw else raw'
parsedRaw <- parseFromString (mconcat <$> many inline) raw'
diff --git a/src/Text/Pandoc/Writers/Markdown.hs b/src/Text/Pandoc/Writers/Markdown.hs
index 662373209..15c6d9fb5 100644
--- a/src/Text/Pandoc/Writers/Markdown.hs
+++ b/src/Text/Pandoc/Writers/Markdown.hs
@@ -57,14 +57,15 @@ import qualified Data.Text as T
type Notes = [[Block]]
type Refs = [([Inline], Target)]
-data WriterState = WriterState { stNotes :: Notes
- , stRefs :: Refs
- , stInList :: Bool
- , stIds :: [String]
- , stPlain :: Bool }
+data WriterState = WriterState { stNotes :: Notes
+ , stRefs :: Refs
+ , stRefShortcutable :: Bool
+ , stInList :: Bool
+ , stIds :: [String]
+ , stPlain :: Bool }
instance Default WriterState
- where def = WriterState{ stNotes = [], stRefs = [], stInList = False,
- stIds = [], stPlain = False }
+ where def = WriterState{ stNotes = [], stRefs = [], stRefShortcutable = True,
+ stInList = False, stIds = [], stPlain = False }
-- | Convert Pandoc to Markdown.
writeMarkdown :: WriterOptions -> Pandoc -> String
@@ -690,27 +691,47 @@ getReference label (src, tit) = do
inlineListToMarkdown :: WriterOptions -> [Inline] -> State WriterState Doc
inlineListToMarkdown opts lst = do
inlist <- gets stInList
- mapM (inlineToMarkdown opts)
- (if inlist then avoidBadWraps lst else lst) >>= return . cat
- where avoidBadWraps [] = []
- avoidBadWraps (Space:Str ('>':cs):xs) =
- Str (' ':'>':cs) : avoidBadWraps xs
- avoidBadWraps (Space:Str [c]:[])
- | c `elem` "-*+" = Str [' ', c] : []
- avoidBadWraps (Space:Str [c]:Space:xs)
- | c `elem` "-*+" = Str [' ', c] : Space : avoidBadWraps xs
- avoidBadWraps (Space:Str cs:Space:xs)
- | isOrderedListMarker cs = Str (' ':cs) : Space : avoidBadWraps xs
- avoidBadWraps (Space:Str cs:[])
- | isOrderedListMarker cs = Str (' ':cs) : []
- avoidBadWraps (x:xs) = x : avoidBadWraps xs
- isOrderedListMarker xs = endsWithListPunct xs &&
- isRight (runParserT (anyOrderedListMarker >> eof)
- defaultParserState "" xs)
- endsWithListPunct xs = case reverse xs of
- '.':_ -> True
- ')':_ -> True
- _ -> False
+ go (if inlist then avoidBadWrapsInList lst else lst)
+ where go [] = return empty
+ go (i:is) = case i of
+ (Link _ _) -> case is of
+ -- If a link is followed by another link or '[' we don't shortcut
+ (Link _ _):_ -> unshortcutable
+ Space:(Link _ _):_ -> unshortcutable
+ Space:(Str('[':_)):_ -> unshortcutable
+ Space:(RawInline _ ('[':_)):_ -> unshortcutable
+ Space:(Cite _ _):_ -> unshortcutable
+ (Cite _ _):_ -> unshortcutable
+ Str ('[':_):_ -> unshortcutable
+ (RawInline _ ('[':_)):_ -> unshortcutable
+ (RawInline _ (' ':'[':_)):_ -> unshortcutable
+ _ -> shortcutable
+ _ -> shortcutable
+ where shortcutable = liftM2 (<>) (inlineToMarkdown opts i) (go is)
+ unshortcutable = do
+ iMark <- withState (\s -> s { stRefShortcutable = False })
+ (inlineToMarkdown opts i)
+ modify (\s -> s {stRefShortcutable = True })
+ fmap (iMark <>) (go is)
+
+avoidBadWrapsInList :: [Inline] -> [Inline]
+avoidBadWrapsInList [] = []
+avoidBadWrapsInList (Space:Str ('>':cs):xs) =
+ Str (' ':'>':cs) : avoidBadWrapsInList xs
+avoidBadWrapsInList (Space:Str [c]:[])
+ | c `elem` "-*+" = Str [' ', c] : []
+avoidBadWrapsInList (Space:Str [c]:Space:xs)
+ | c `elem` "-*+" = Str [' ', c] : Space : avoidBadWrapsInList xs
+avoidBadWrapsInList (Space:Str cs:Space:xs)
+ | isOrderedListMarker cs = Str (' ':cs) : Space : avoidBadWrapsInList xs
+avoidBadWrapsInList (Space:Str cs:[])
+ | isOrderedListMarker cs = Str (' ':cs) : []
+avoidBadWrapsInList (x:xs) = x : avoidBadWrapsInList xs
+
+isOrderedListMarker :: String -> Bool
+isOrderedListMarker xs = (last xs `elem` ".)") &&
+ isRight (runParserT (anyOrderedListMarker >> eof)
+ defaultParserState "" xs)
isRight :: Either a b -> Bool
isRight (Right _) = True
@@ -873,6 +894,9 @@ inlineToMarkdown opts (Link txt (src, tit)) = do
[Str s] | escapeURI s == srcSuffix -> True
_ -> False
let useRefLinks = writerReferenceLinks opts && not useAuto
+ shortcutable <- gets stRefShortcutable
+ let useShortcutRefLinks = shortcutable &&
+ isEnabled Ext_shortcut_reference_links opts
ref <- if useRefLinks then getReference txt (src, tit) else return []
reftext <- inlineListToMarkdown opts ref
return $ if useAuto
@@ -882,7 +906,9 @@ inlineToMarkdown opts (Link txt (src, tit)) = do
else if useRefLinks
then let first = "[" <> linktext <> "]"
second = if txt == ref
- then "[]"
+ then if useShortcutRefLinks
+ then ""
+ else "[]"
else "[" <> reftext <> "]"
in first <> second
else if plain