diff options
Diffstat (limited to 'src')
-rw-r--r-- | src/Text/Pandoc/Extensions.hs | 3 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/CommonMark.hs | 7 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/Markdown.hs | 3 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/Org/Inlines.hs | 31 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/Org/Shared.hs | 3 | ||||
-rw-r--r-- | src/Text/Pandoc/Shared.hs | 32 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/CommonMark.hs | 27 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/DokuWiki.hs | 8 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/EPUB.hs | 1 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/HTML.hs | 22 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/LaTeX.hs | 16 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/Markdown.hs | 6 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/ZimWiki.hs | 8 |
13 files changed, 121 insertions, 46 deletions
diff --git a/src/Text/Pandoc/Extensions.hs b/src/Text/Pandoc/Extensions.hs index f2599ed6d..f660cf766 100644 --- a/src/Text/Pandoc/Extensions.hs +++ b/src/Text/Pandoc/Extensions.hs @@ -167,6 +167,7 @@ data Extension = | Ext_subscript -- ^ Subscript using ~this~ syntax | Ext_superscript -- ^ Superscript using ^this^ syntax | Ext_styles -- ^ Read styles that pandoc doesn't know + | Ext_task_lists -- ^ Parse certain list items as task list items | Ext_table_captions -- ^ Pandoc-style table captions | Ext_tex_math_dollars -- ^ TeX math between $..$ or $$..$$ | Ext_tex_math_double_backslash -- ^ TeX math btw \\(..\\) \\[..\\] @@ -215,6 +216,7 @@ pandocExtensions = extensionsFromList , Ext_strikeout , Ext_superscript , Ext_subscript + , Ext_task_lists , Ext_auto_identifiers , Ext_header_attributes , Ext_link_attributes @@ -274,6 +276,7 @@ githubMarkdownExtensions = extensionsFromList , Ext_space_in_atx_header , Ext_intraword_underscores , Ext_strikeout + , Ext_task_lists , Ext_emoji , Ext_lists_without_preceding_blankline , Ext_shortcut_reference_links 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 = diff --git a/src/Text/Pandoc/Shared.hs b/src/Text/Pandoc/Shared.hs index 9fa083c11..4efdbba61 100644 --- a/src/Text/Pandoc/Shared.hs +++ b/src/Text/Pandoc/Shared.hs @@ -79,6 +79,8 @@ module Text.Pandoc.Shared ( headerShift, stripEmptyParagraphs, isTightList, + taskListItemFromAscii, + taskListItemToAscii, addMetaField, makeMeta, eastAsianLineBreakFilter, @@ -588,6 +590,36 @@ isTightList = all firstIsPlain where firstIsPlain (Plain _ : _) = True firstIsPlain _ = False +-- | Convert a list item containing tasklist syntax (e.g. @[x]@) +-- to using @U+2610 BALLOT BOX@ or @U+2612 BALLOT BOX WITH X@. +taskListItemFromAscii :: Extensions -> [Block] -> [Block] +taskListItemFromAscii = handleTaskListItem fromMd + where + fromMd (Str "[" : Space : Str "]" : Space : is) = (Str "☐") : Space : is + fromMd (Str "[x]" : Space : is) = (Str "☒") : Space : is + fromMd (Str "[X]" : Space : is) = (Str "☒") : Space : is + fromMd is = is + +-- | Convert a list item containing text starting with @U+2610 BALLOT BOX@ +-- or @U+2612 BALLOT BOX WITH X@ to tasklist syntax (e.g. @[x]@). +taskListItemToAscii :: Extensions -> [Block] -> [Block] +taskListItemToAscii = handleTaskListItem toMd + where + toMd (Str "☐" : Space : is) = rawMd "[ ]" : Space : is + toMd (Str "☒" : Space : is) = rawMd "[x]" : Space : is + toMd is = is + rawMd = RawInline (Format "markdown") + +handleTaskListItem :: ([Inline] -> [Inline]) -> Extensions -> [Block] -> [Block] +handleTaskListItem handleInlines exts bls = + if Ext_task_lists `extensionEnabled` exts + then handleItem bls + else bls + where + handleItem (Plain is : bs) = Plain (handleInlines is) : bs + handleItem (Para is : bs) = Para (handleInlines is) : bs + handleItem bs = bs + -- | Set a field of a 'Meta' object. If the field already has a value, -- convert it into a list with the new value appended to the old value(s). addMetaField :: ToMetaValue a diff --git a/src/Text/Pandoc/Writers/CommonMark.hs b/src/Text/Pandoc/Writers/CommonMark.hs index c007f7734..e28fa71a9 100644 --- a/src/Text/Pandoc/Writers/CommonMark.hs +++ b/src/Text/Pandoc/Writers/CommonMark.hs @@ -46,7 +46,8 @@ import Network.HTTP (urlEncode) import Text.Pandoc.Class (PandocMonad) import Text.Pandoc.Definition import Text.Pandoc.Options -import Text.Pandoc.Shared (isTightList, linesToPara, substitute, capitalize) +import Text.Pandoc.Shared (isTightList, taskListItemToAscii, linesToPara, + substitute, capitalize) import Text.Pandoc.Templates (renderTemplate') import Text.Pandoc.Walk (query, walk, walkM) import Text.Pandoc.Writers.HTML (writeHtml5String, tagWithAttributes) @@ -115,24 +116,28 @@ blockToNodes opts (Para xs) ns = blockToNodes opts (LineBlock lns) ns = blockToNodes opts (linesToPara lns) ns blockToNodes _ (CodeBlock (_,classes,_) xs) ns = return (node (CODE_BLOCK (T.pack (unwords classes)) (T.pack xs)) [] : ns) -blockToNodes opts (RawBlock fmt xs) ns - | fmt == Format "html" && isEnabled Ext_raw_html opts +blockToNodes opts (RawBlock (Format f) xs) ns + | f == "html" && isEnabled Ext_raw_html opts = return (node (HTML_BLOCK (T.pack xs)) [] : ns) - | (fmt == Format "latex" || fmt == Format "tex") && isEnabled Ext_raw_tex opts + | (f == "latex" || f == "tex") && isEnabled Ext_raw_tex opts + = return (node (CUSTOM_BLOCK (T.pack xs) T.empty) [] : ns) + | f == "markdown" = return (node (CUSTOM_BLOCK (T.pack xs) T.empty) [] : ns) | otherwise = return ns blockToNodes opts (BlockQuote bs) ns = do nodes <- blocksToNodes opts bs return (node BLOCK_QUOTE nodes : ns) blockToNodes opts (BulletList items) ns = do - nodes <- mapM (blocksToNodes opts) items + let exts = writerExtensions opts + nodes <- mapM (blocksToNodes opts . taskListItemToAscii exts) items return (node (LIST ListAttributes{ listType = BULLET_LIST, listDelim = PERIOD_DELIM, listTight = isTightList items, listStart = 1 }) (map (node ITEM) nodes) : ns) blockToNodes opts (OrderedList (start, _sty, delim) items) ns = do - nodes <- mapM (blocksToNodes opts) items + let exts = writerExtensions opts + nodes <- mapM (blocksToNodes opts . taskListItemToAscii exts) items return (node (LIST ListAttributes{ listType = ORDERED_LIST, listDelim = case delim of @@ -247,7 +252,7 @@ inlineToNodes opts (Str s) = stringToNodes opts s' inlineToNodes _ Space = (node (TEXT (T.pack " ")) [] :) inlineToNodes _ LineBreak = (node LINEBREAK [] :) inlineToNodes opts SoftBreak - | isEnabled Ext_hard_line_breaks opts = (node LINEBREAK [] :) + | isEnabled Ext_hard_line_breaks opts = (node (TEXT " ") [] :) | writerWrapText opts == WrapNone = (node (TEXT " ") [] :) | otherwise = (node SOFTBREAK [] :) inlineToNodes opts (Emph xs) = (node EMPH (inlinesToNodes opts xs) :) @@ -292,10 +297,12 @@ inlineToNodes opts (Image alt ils (url,'f':'i':'g':':':tit)) = inlineToNodes opts (Image alt ils (url,tit)) inlineToNodes opts (Image _ ils (url,tit)) = (node (IMAGE (T.pack url) (T.pack tit)) (inlinesToNodes opts ils) :) -inlineToNodes opts (RawInline fmt xs) - | fmt == Format "html" && isEnabled Ext_raw_html opts +inlineToNodes opts (RawInline (Format f) xs) + | f == "html" && isEnabled Ext_raw_html opts = (node (HTML_INLINE (T.pack xs)) [] :) - | (fmt == Format "latex" || fmt == Format "tex") && isEnabled Ext_raw_tex opts + | (f == "latex" || f == "tex") && isEnabled Ext_raw_tex opts + = (node (CUSTOM_INLINE (T.pack xs) T.empty) [] :) + | f == "markdown" = (node (CUSTOM_INLINE (T.pack xs) T.empty) [] :) | otherwise = id inlineToNodes opts (Quoted qt ils) = diff --git a/src/Text/Pandoc/Writers/DokuWiki.hs b/src/Text/Pandoc/Writers/DokuWiki.hs index 28426af67..5992857cc 100644 --- a/src/Text/Pandoc/Writers/DokuWiki.hs +++ b/src/Text/Pandoc/Writers/DokuWiki.hs @@ -130,9 +130,7 @@ blockToDokuWiki opts (Para [Image attr txt (src,'f':'i':'g':':':tit)]) = do let opt = if null txt then "" else "|" ++ if null tit then capt else tit ++ capt - -- Relative links fail isURI and receive a colon - prefix = if isURI src then "" else ":" - return $ "{{" ++ prefix ++ src ++ imageDims opts attr ++ opt ++ "}}\n" + return $ "{{" ++ src ++ imageDims opts attr ++ opt ++ "}}\n" blockToDokuWiki opts (Para inlines) = do indent <- asks stIndent @@ -516,9 +514,7 @@ inlineToDokuWiki opts (Image attr alt (source, tit)) = do ("", []) -> "" ("", _ ) -> "|" ++ alt' (_ , _ ) -> "|" ++ tit - -- Relative links fail isURI and receive a colon - prefix = if isURI source then "" else ":" - return $ "{{" ++ prefix ++ source ++ imageDims opts attr ++ txt ++ "}}" + return $ "{{" ++ source ++ imageDims opts attr ++ txt ++ "}}" inlineToDokuWiki opts (Note contents) = do contents' <- blockListToDokuWiki opts contents diff --git a/src/Text/Pandoc/Writers/EPUB.hs b/src/Text/Pandoc/Writers/EPUB.hs index 93c685ffa..4faaa1631 100644 --- a/src/Text/Pandoc/Writers/EPUB.hs +++ b/src/Text/Pandoc/Writers/EPUB.hs @@ -814,6 +814,7 @@ pandocToEPUB version opts doc@(Pandoc meta _) = do let landmarks = if epub3 then [RawBlock (Format "html") $ ppElement $ unode "nav" ! [("epub:type","landmarks") + ,("id","landmarks") ,("hidden","hidden")] $ [ unode "ol" $ [ unode "li" diff --git a/src/Text/Pandoc/Writers/HTML.hs b/src/Text/Pandoc/Writers/HTML.hs index 8cdadca5b..98b86a7c9 100644 --- a/src/Text/Pandoc/Writers/HTML.hs +++ b/src/Text/Pandoc/Writers/HTML.hs @@ -365,6 +365,24 @@ defList :: PandocMonad m => WriterOptions -> [Html] -> StateT WriterState m Html defList opts items = toList H.dl opts (items ++ [nl opts]) +listItemToHtml :: PandocMonad m + => WriterOptions -> [Block] -> StateT WriterState m Html +listItemToHtml opts bls + | Plain (Str "☐":Space:is) : bs <- bls = taskListItem False id is bs + | Plain (Str "☒":Space:is) : bs <- bls = taskListItem True id is bs + | Para (Str "☐":Space:is) : bs <- bls = taskListItem False H.p is bs + | Para (Str "☒":Space:is) : bs <- bls = taskListItem True H.p is bs + | otherwise = blockListToHtml opts bls + where + taskListItem checked constr is bs = do + let checkbox = if checked + then checkbox' ! A.checked "" + else checkbox' + checkbox' = H.input ! A.type_ "checkbox" ! A.disabled "" >> nl opts + isContents <- inlineListToHtml opts is + bsContents <- blockListToHtml opts bs + return $ constr (checkbox >> isContents) >> bsContents + -- | Construct table of contents from list of elements. tableOfContents :: PandocMonad m => WriterOptions -> [Element] -> StateT WriterState m (Maybe Html) @@ -824,10 +842,10 @@ blockToHtml opts (Header level attr@(_,classes,_) lst) = do 6 -> H.h6 contents' _ -> H.p contents' blockToHtml opts (BulletList lst) = do - contents <- mapM (blockListToHtml opts) lst + contents <- mapM (listItemToHtml opts) lst unordList opts contents blockToHtml opts (OrderedList (startnum, numstyle, _) lst) = do - contents <- mapM (blockListToHtml opts) lst + contents <- mapM (listItemToHtml opts) lst html5 <- gets stHtml5 let numstyle' = case numstyle of Example -> "decimal" diff --git a/src/Text/Pandoc/Writers/LaTeX.hs b/src/Text/Pandoc/Writers/LaTeX.hs index f9bee886e..7441152a6 100644 --- a/src/Text/Pandoc/Writers/LaTeX.hs +++ b/src/Text/Pandoc/Writers/LaTeX.hs @@ -924,8 +924,20 @@ listItemToLaTeX lst -- this will keep the typesetter from throwing an error. | (Header{} :_) <- lst = blockListToLaTeX lst >>= return . (text "\\item ~" $$) . nest 2 - | otherwise = blockListToLaTeX lst >>= return . (text "\\item" $$) . - nest 2 + | Plain (Str "☐":Space:is) : bs <- lst = taskListItem False is bs + | Plain (Str "☒":Space:is) : bs <- lst = taskListItem True is bs + | Para (Str "☐":Space:is) : bs <- lst = taskListItem False is bs + | Para (Str "☒":Space:is) : bs <- lst = taskListItem True is bs + | otherwise = blockListToLaTeX lst >>= return . (text "\\item" $$) . nest 2 + where + taskListItem checked is bs = do + let checkbox = if checked + then "$\\boxtimes$" + else "$\\square$" + isContents <- inlineListToLaTeX is + bsContents <- blockListToLaTeX bs + return $ "\\item" <> brackets checkbox + $$ nest 2 (isContents $+$ bsContents) defListItemToLaTeX :: PandocMonad m => ([Inline], [[Block]]) -> LW m Doc defListItemToLaTeX (term, defs) = do diff --git a/src/Text/Pandoc/Writers/Markdown.hs b/src/Text/Pandoc/Writers/Markdown.hs index c0c6e8ebf..7babbe982 100644 --- a/src/Text/Pandoc/Writers/Markdown.hs +++ b/src/Text/Pandoc/Writers/Markdown.hs @@ -765,7 +765,8 @@ itemEndsWithTightList bs = -- | Convert bullet list item (list of blocks) to markdown. bulletListItemToMarkdown :: PandocMonad m => WriterOptions -> [Block] -> MD m Doc bulletListItemToMarkdown opts bs = do - contents <- blockListToMarkdown opts bs + let exts = writerExtensions opts + contents <- blockListToMarkdown opts $ taskListItemToAscii exts bs let sps = replicate (writerTabStop opts - 2) ' ' let start = text ('-' : ' ' : sps) -- remove trailing blank line if item ends with a tight list @@ -781,7 +782,8 @@ orderedListItemToMarkdown :: PandocMonad m -> [Block] -- ^ list item (list of blocks) -> MD m Doc orderedListItemToMarkdown opts marker bs = do - contents <- blockListToMarkdown opts bs + let exts = writerExtensions opts + contents <- blockListToMarkdown opts $ taskListItemToAscii exts bs let sps = case length marker - writerTabStop opts of n | n > 0 -> text $ replicate n ' ' _ -> text " " diff --git a/src/Text/Pandoc/Writers/ZimWiki.hs b/src/Text/Pandoc/Writers/ZimWiki.hs index 84b60fdfe..4d0680bc9 100644 --- a/src/Text/Pandoc/Writers/ZimWiki.hs +++ b/src/Text/Pandoc/Writers/ZimWiki.hs @@ -109,9 +109,7 @@ blockToZimWiki opts (Para [Image attr txt (src,'f':'i':'g':':':tit)]) = do let opt = if null txt then "" else "|" ++ if null tit then capt else tit ++ capt - -- Relative links fail isURI and receive a colon - prefix = if isURI src then "" else ":" - return $ "{{" ++ prefix ++ src ++ imageDims opts attr ++ opt ++ "}}\n" + return $ "{{" ++ src ++ imageDims opts attr ++ opt ++ "}}\n" blockToZimWiki opts (Para inlines) = do indent <- gets stIndent @@ -383,9 +381,7 @@ inlineToZimWiki opts (Image attr alt (source, tit)) = do ("", _, False ) -> "|" ++ alt' (_ , _, False ) -> "|" ++ tit (_ , _, True ) -> "" - -- Relative links fail isURI and receive a colon - prefix = if isURI source then "" else ":" - return $ "{{" ++ prefix ++ source ++ imageDims opts attr ++ txt ++ "}}" + return $ "{{" ++ source ++ imageDims opts attr ++ txt ++ "}}" inlineToZimWiki opts (Note contents) = do -- no concept of notes in zim wiki, use a text block |