aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Readers
diff options
context:
space:
mode:
Diffstat (limited to 'src/Text/Pandoc/Readers')
-rw-r--r--src/Text/Pandoc/Readers/CommonMark.hs7
-rw-r--r--src/Text/Pandoc/Readers/Markdown.hs3
-rw-r--r--src/Text/Pandoc/Readers/Org/Inlines.hs31
-rw-r--r--src/Text/Pandoc/Readers/Org/Shared.hs3
4 files changed, 26 insertions, 18 deletions
diff --git a/src/Text/Pandoc/Readers/CommonMark.hs b/src/Text/Pandoc/Readers/CommonMark.hs
index 3cc75e2a1..0a3f5e51d 100644
--- a/src/Text/Pandoc/Readers/CommonMark.hs
+++ b/src/Text/Pandoc/Readers/CommonMark.hs
@@ -43,7 +43,7 @@ import Text.Pandoc.Class (PandocMonad)
import Text.Pandoc.Definition
import Text.Pandoc.Emoji (emojiToInline)
import Text.Pandoc.Options
-import Text.Pandoc.Shared (uniqueIdent)
+import Text.Pandoc.Shared (uniqueIdent, taskListItemFromAscii)
import Text.Pandoc.Walk (walkM)
-- | Parse a CommonMark formatted string into a 'Pandoc' structure.
@@ -111,12 +111,14 @@ addBlock _ (Node _ (CODE_BLOCK info t) _) =
addBlock opts (Node _ (HEADING lev) nodes) =
(Header lev ("",[],[]) (addInlines opts nodes) :)
addBlock opts (Node _ (LIST listAttrs) nodes) =
- (constructor (map (setTightness . addBlocks opts . children) nodes) :)
+ (constructor (map listItem nodes) :)
where constructor = case listType listAttrs of
BULLET_LIST -> BulletList
ORDERED_LIST -> OrderedList
(start, DefaultStyle, delim)
start = listStart listAttrs
+ listItem = taskListItemFromAscii exts . setTightness
+ . addBlocks opts . children
setTightness = if listTight listAttrs
then map paraToPlain
else id
@@ -125,6 +127,7 @@ addBlock opts (Node _ (LIST listAttrs) nodes) =
delim = case listDelim listAttrs of
PERIOD_DELIM -> Period
PAREN_DELIM -> OneParen
+ exts = readerExtensions opts
addBlock opts (Node _ (TABLE alignments) nodes) =
(Table [] aligns widths headers rows :)
where aligns = map fromTableCellAlignment alignments
diff --git a/src/Text/Pandoc/Readers/Markdown.hs b/src/Text/Pandoc/Readers/Markdown.hs
index 94d1157a6..dd1bedc91 100644
--- a/src/Text/Pandoc/Readers/Markdown.hs
+++ b/src/Text/Pandoc/Readers/Markdown.hs
@@ -958,7 +958,8 @@ listItem fourSpaceRule start = try $ do
let raw = concat (first:continuations)
contents <- parseFromString' parseBlocks raw
updateState (\st -> st {stateParserContext = oldContext})
- return contents
+ exts <- getOption readerExtensions
+ return $ B.fromList . taskListItemFromAscii exts . B.toList <$> contents
orderedList :: PandocMonad m => MarkdownParser m (F Blocks)
orderedList = try $ do
diff --git a/src/Text/Pandoc/Readers/Org/Inlines.hs b/src/Text/Pandoc/Readers/Org/Inlines.hs
index dfe398130..6560def7e 100644
--- a/src/Text/Pandoc/Readers/Org/Inlines.hs
+++ b/src/Text/Pandoc/Readers/Org/Inlines.hs
@@ -432,21 +432,28 @@ explicitOrImageLink :: PandocMonad m => OrgParser m (F Inlines)
explicitOrImageLink = try $ do
char '['
srcF <- applyCustomLinkFormat =<< possiblyEmptyLinkTarget
- title <- enclosedRaw (char '[') (char ']')
- title' <- parseFromString (mconcat <$> many inline) title
+ descr <- enclosedRaw (char '[') (char ']')
+ titleF <- parseFromString (mconcat <$> many inline) descr
char ']'
return $ do
src <- srcF
- case cleanLinkString title of
+ title <- titleF
+ case cleanLinkString descr of
Just imgSrc | isImageFilename imgSrc ->
- pure . B.link src "" $ B.image imgSrc mempty mempty
+ return . B.link src "" $ B.image imgSrc mempty mempty
_ ->
- linkToInlinesF src =<< title'
+ linkToInlinesF src title
selflinkOrImage :: PandocMonad m => OrgParser m (F Inlines)
selflinkOrImage = try $ do
- src <- char '[' *> linkTarget <* char ']'
- return $ linkToInlinesF src (B.str src)
+ target <- char '[' *> linkTarget <* char ']'
+ case cleanLinkString target of
+ Nothing -> case target of
+ '#':_ -> returnF $ B.link target "" (B.str target)
+ _ -> return $ internalLink target (B.str target)
+ Just nonDocTgt -> if isImageFilename nonDocTgt
+ then returnF $ B.image nonDocTgt "" ""
+ else returnF $ B.link nonDocTgt "" (B.str target)
plainLink :: PandocMonad m => OrgParser m (F Inlines)
plainLink = try $ do
@@ -481,10 +488,8 @@ linkToInlinesF linkStr =
"" -> pure . B.link mempty "" -- wiki link (empty by convention)
('#':_) -> pure . B.link linkStr "" -- document-local fraction
_ -> case cleanLinkString linkStr of
- (Just cleanedLink) -> if isImageFilename cleanedLink
- then const . pure $ B.image cleanedLink "" ""
- else pure . B.link cleanedLink ""
- Nothing -> internalLink linkStr -- other internal link
+ Just extTgt -> return . B.link extTgt ""
+ Nothing -> internalLink linkStr -- other internal link
internalLink :: String -> Inlines -> F Inlines
internalLink link title = do
@@ -530,7 +535,7 @@ inlineCodeBlock = try $ do
let attrClasses = [translateLang lang]
let attrKeyVal = originalLang lang <> opts
let codeInlineBlck = B.codeWith ("", attrClasses, attrKeyVal) inlineCode
- returnF $ (if exportsCode opts then codeInlineBlck else mempty)
+ returnF $ if exportsCode opts then codeInlineBlck else mempty
where
inlineBlockOption :: PandocMonad m => OrgParser m (String, String)
inlineBlockOption = try $ do
@@ -739,7 +744,7 @@ many1TillNOrLessNewlines n p end = try $
rest m cs = (\x -> (minus1 <$> m, cs ++ x ++ "\n")) <$> try (manyTill p newline)
finalLine = try $ manyTill p end
minus1 k = k - 1
- oneOrMore cs = guard (not $ null cs) *> return cs
+ oneOrMore cs = cs <$ guard (not $ null cs)
-- Org allows customization of the way it reads emphasis. We use the defaults
-- here (see, e.g., the Emacs Lisp variable `org-emphasis-regexp-components`
diff --git a/src/Text/Pandoc/Readers/Org/Shared.hs b/src/Text/Pandoc/Readers/Org/Shared.hs
index 71d1dd517..9e7ef9930 100644
--- a/src/Text/Pandoc/Readers/Org/Shared.hs
+++ b/src/Text/Pandoc/Readers/Org/Shared.hs
@@ -61,8 +61,7 @@ cleanLinkString s =
'.':'.':'/':_ -> Just s -- relative path
-- Relative path or URL (file schema)
'f':'i':'l':'e':':':s' -> Just $ if "//" `isPrefixOf` s' then s else s'
- _ | isUrl s -> Just s -- URL
- _ -> Nothing
+ _ -> if isUrl s then Just s else Nothing
where
isUrl :: String -> Bool
isUrl cs =