aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--MANUAL.txt18
-rw-r--r--Setup.hs38
-rw-r--r--data/epub.css7
-rw-r--r--pandoc.cabal5
-rw-r--r--src/Text/Pandoc/Extensions.hs3
-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
-rw-r--r--src/Text/Pandoc/Shared.hs32
-rw-r--r--src/Text/Pandoc/Writers/CommonMark.hs27
-rw-r--r--src/Text/Pandoc/Writers/DokuWiki.hs8
-rw-r--r--src/Text/Pandoc/Writers/EPUB.hs1
-rw-r--r--src/Text/Pandoc/Writers/HTML.hs22
-rw-r--r--src/Text/Pandoc/Writers/LaTeX.hs16
-rw-r--r--src/Text/Pandoc/Writers/Markdown.hs6
-rw-r--r--src/Text/Pandoc/Writers/ZimWiki.hs8
-rw-r--r--test/Tests/Readers/Org/Inline.hs34
-rw-r--r--test/command/5195.md7
-rw-r--r--test/command/gfm.md29
-rw-r--r--test/command/tasklist.md113
-rw-r--r--test/dokuwiki_external_images.dokuwiki2
-rw-r--r--test/writer.dokuwiki4
-rw-r--r--test/writer.zimwiki4
24 files changed, 314 insertions, 114 deletions
diff --git a/MANUAL.txt b/MANUAL.txt
index a81720eb5..9cdf58772 100644
--- a/MANUAL.txt
+++ b/MANUAL.txt
@@ -2612,6 +2612,12 @@ If default list markers are desired, use `#.`:
#. two
#. three
+#### Extension: `task_lists` ####
+
+Pandoc supports task lists, using the syntax of GitHub-Flavored Markdown.
+
+ - [ ] an unchecked task list item
+ - [x] checked item
### Definition lists ###
@@ -4223,7 +4229,7 @@ variants are supported:
: `pipe_tables`, `raw_html`, `fenced_code_blocks`, `auto_identifiers`,
`gfm_auto_identifiers`, `backtick_code_blocks`,
`autolink_bare_uris`, `space_in_atx_header`,
- `intraword_underscores`, `strikeout`, `emoji`,
+ `intraword_underscores`, `strikeout`, `task_lists`, `emoji`,
`shortcut_reference_links`, `angle_brackets_escapable`,
`lists_without_preceding_blankline`.
@@ -4245,16 +4251,16 @@ We also support `commonmark` and `gfm` (GitHub-Flavored Markdown,
which is implemented as a set of extensions on `commonmark`).
Note, however, that `commonmark` and `gfm` have limited support
-for extensions. Only those listed below (and `smart` and
-`raw_tex`) will work. The extensions can, however, all be
-individually disabled.
-Also, `raw_tex` only affects `gfm` output, not input.
+for extensions. Only those listed below (and `smart`,
+`raw_tex`, and `hard_line_breaks`) will work. The extensions
+can, however, all be individually disabled. Also, `raw_tex`
+only affects `gfm` output, not input.
`gfm` (GitHub-Flavored Markdown)
: `pipe_tables`, `raw_html`, `fenced_code_blocks`, `auto_identifiers`,
`gfm_auto_identifiers`, `backtick_code_blocks`,
`autolink_bare_uris`, `space_in_atx_header`,
- `intraword_underscores`, `strikeout`, `emoji`,
+ `intraword_underscores`, `strikeout`, `task_lists`, `emoji`,
`shortcut_reference_links`, `angle_brackets_escapable`,
`lists_without_preceding_blankline`.
diff --git a/Setup.hs b/Setup.hs
index 889004bc0..9a994af67 100644
--- a/Setup.hs
+++ b/Setup.hs
@@ -1,38 +1,2 @@
-{-
-Copyright (C) 2006-2018 John MacFarlane <jgm@berkeley.edu>
-
-This program is free software; you can redistribute it and/or modify
-it under the terms of the GNU General Public License as published by
-the Free Software Foundation; either version 2 of the License, or
-(at your option) any later version.
-
-This program is distributed in the hope that it will be useful,
-but WITHOUT ANY WARRANTY; without even the implied warranty of
-MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
-GNU General Public License for more details.
-
-You should have received a copy of the GNU General Public License
-along with this program; if not, write to the Free Software
-Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
--}
-
import Distribution.Simple
-import Distribution.Simple.Setup (CopyFlags(..), fromFlag)
-import Distribution.PackageDescription (PackageDescription(..))
-import Distribution.Simple.Utils (notice, installOrdinaryFiles)
-import Distribution.Simple.LocalBuildInfo
-
-main :: IO ()
-main = defaultMainWithHooks $ simpleUserHooks {
- postCopy = installManPage
- }
-
-installManPage :: Args -> CopyFlags
- -> PackageDescription -> LocalBuildInfo -> IO ()
-installManPage _ flags pkg lbi = do
- let verbosity = fromFlag (copyVerbosity flags)
- let copydest = fromFlag (copyDest flags)
- let mandest = mandir (absoluteInstallDirs pkg lbi copydest)
- ++ "/man1"
- notice verbosity $ "Copying man page to " ++ mandest
- installOrdinaryFiles verbosity mandest [("man", "pandoc.1")]
+main = defaultMain
diff --git a/data/epub.css b/data/epub.css
index 34835ced4..742ea7895 100644
--- a/data/epub.css
+++ b/data/epub.css
@@ -10,9 +10,10 @@ h6 { text-align: left; }
h1.title { }
h2.author { }
h3.date { }
-ol.toc { padding: 0; margin-left: 1em; }
-ol.toc li { list-style-type: none; margin: 0; padding: 0; }
+nav#toc ol,
+nav#landmarks ol { padding: 0; margin-left: 1em; }
+nav#toc ol li,
+nav#landmarks ol li { list-style-type: none; margin: 0; padding: 0; }
a.footnote-ref { vertical-align: super; }
em, em em em, em em em em em { font-style: italic;}
em em, em em em em { font-style: normal; }
-
diff --git a/pandoc.cabal b/pandoc.cabal
index 6f0abf693..c23552c08 100644
--- a/pandoc.cabal
+++ b/pandoc.cabal
@@ -1,7 +1,7 @@
name: pandoc
version: 2.6
cabal-version: 2.0
-build-type: Custom
+build-type: Simple
license: GPL-2
license-file: COPYING.md
copyright: (c) 2006-2018 John MacFarlane
@@ -346,9 +346,6 @@ flag trypandoc
Description: Build trypandoc cgi executable.
Default: False
-custom-setup
- setup-depends: base, Cabal >= 2.0
-
library
build-depends: base >= 4.8 && < 5,
syb >= 0.1 && < 0.8,
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
diff --git a/test/Tests/Readers/Org/Inline.hs b/test/Tests/Readers/Org/Inline.hs
index 9cfcda79f..e5996d4d8 100644
--- a/test/Tests/Readers/Org/Inline.hs
+++ b/test/Tests/Readers/Org/Inline.hs
@@ -184,26 +184,26 @@ tests =
, testGroup "Images"
[ "Image" =:
- "[[./sunset.jpg]]" =?>
- para (image "./sunset.jpg" "" "")
+ "[[./sunset.jpg]]" =?>
+ para (image "./sunset.jpg" "" "")
, "Image with explicit file: prefix" =:
- "[[file:sunrise.jpg]]" =?>
- para (image "sunrise.jpg" "" "")
+ "[[file:sunrise.jpg]]" =?>
+ para (image "sunrise.jpg" "" "")
, "Multiple images within a paragraph" =:
- T.unlines [ "[[file:sunrise.jpg]]"
- , "[[file:sunset.jpg]]"
- ] =?>
- para ((image "sunrise.jpg" "" "")
+ T.unlines [ "[[file:sunrise.jpg]]"
+ , "[[file:sunset.jpg]]"
+ ] =?>
+ para (image "sunrise.jpg" "" ""
<> softbreak
- <> (image "sunset.jpg" "" ""))
+ <> image "sunset.jpg" "" "")
, "Image with html attributes" =:
- T.unlines [ "#+ATTR_HTML: :width 50%"
- , "[[file:guinea-pig.gif]]"
- ] =?>
- para (imageWith ("", [], [("width", "50%")]) "guinea-pig.gif" "" "")
+ T.unlines [ "#+ATTR_HTML: :width 50%"
+ , "[[file:guinea-pig.gif]]"
+ ] =?>
+ para (imageWith ("", [], [("width", "50%")]) "guinea-pig.gif" "" "")
]
, "Explicit link" =:
@@ -215,6 +215,10 @@ tests =
"[[http://zeitlens.com/]]" =?>
para (link "http://zeitlens.com/" "" "http://zeitlens.com/")
+ , "Internal self-link (reference)" =:
+ "[[#rabbit]]" =?>
+ para (link "#rabbit" "" "#rabbit")
+
, "Absolute file link" =:
"[[/url][hi]]" =?>
para (link "file:///url" "" "hi")
@@ -235,6 +239,10 @@ tests =
"[[http://example.com][./logo.png]]" =?>
para (link "http://example.com" "" (image "./logo.png" "" ""))
+ , "Link to image" =:
+ "[[https://example.com/image.jpg][Look!]]" =?>
+ para (link "https://example.com/image.jpg" "" (str "Look!"))
+
, "Plain link" =:
"Posts on http://zeitlens.com/ can be funny at times." =?>
para (spcSep [ "Posts", "on"
diff --git a/test/command/5195.md b/test/command/5195.md
new file mode 100644
index 000000000..10c542eb0
--- /dev/null
+++ b/test/command/5195.md
@@ -0,0 +1,7 @@
+```
+% pandoc -f markdown_strict -t gfm+hard_line_breaks
+Hello
+there
+^D
+Hello there
+```
diff --git a/test/command/gfm.md b/test/command/gfm.md
index 7a7098989..a4bb088b6 100644
--- a/test/command/gfm.md
+++ b/test/command/gfm.md
@@ -101,3 +101,32 @@ hi
^D
[Para [Str "hi",LineBreak,Str "hi"]]
```
+
+```
+% pandoc -f gfm -t native
+- [ ] foo
+- [x] bar
+^D
+[BulletList
+ [[Plain [Str "\9744",Space,Str "foo"]]
+ ,[Plain [Str "\9746",Space,Str "bar"]]]]
+```
+
+```
+% pandoc -f gfm-task_lists -t native
+- [ ] foo
+- [x] bar
+^D
+[BulletList
+ [[Plain [Str "[",Space,Str "]",Space,Str "foo"]]
+ ,[Plain [Str "[x]",Space,Str "bar"]]]]
+```
+
+```
+% pandoc -f gfm -t gfm
+- [ ] foo
+- [x] bar
+^D
+ - [ ] foo
+ - [x] bar
+```
diff --git a/test/command/tasklist.md b/test/command/tasklist.md
new file mode 100644
index 000000000..5ff628e1c
--- /dev/null
+++ b/test/command/tasklist.md
@@ -0,0 +1,113 @@
+tests adapted from <https://github.github.com/gfm/#task-list-items-extension->
+
+```
+% pandoc
+- [ ] foo
+- [x] bar
+^D
+<ul>
+<li><input type="checkbox" disabled="" />
+foo</li>
+<li><input type="checkbox" disabled="" checked="" />
+bar</li>
+</ul>
+```
+
+
+```
+% pandoc
+- [x] foo
+ - [ ] bar
+ - [x] baz
+- [ ] bim
+^D
+<ul>
+<li><input type="checkbox" disabled="" checked="" />
+foo<ul>
+<li><input type="checkbox" disabled="" />
+bar</li>
+<li><input type="checkbox" disabled="" checked="" />
+baz</li>
+</ul></li>
+<li><input type="checkbox" disabled="" />
+bim</li>
+</ul>
+```
+
+
+custom html task list test:
+
+```
+% pandoc
+- [ ] unchecked
+- plain item
+- [x] checked
+
+paragraph
+
+1. [ ] ordered unchecked
+2. [] plain item
+3. [x] ordered checked
+
+paragraph
+
+- [ ] list item with a
+
+ second paragraph
+
+- [x] checked
+^D
+<ul>
+<li><input type="checkbox" disabled="" />
+unchecked</li>
+<li>plain item</li>
+<li><input type="checkbox" disabled="" checked="" />
+checked</li>
+</ul>
+<p>paragraph</p>
+<ol type="1">
+<li><input type="checkbox" disabled="" />
+ordered unchecked</li>
+<li>[] plain item</li>
+<li><input type="checkbox" disabled="" checked="" />
+ordered checked</li>
+</ol>
+<p>paragraph</p>
+<ul>
+<li><p><input type="checkbox" disabled="" />
+list item with a</p><p>second paragraph</p></li>
+<li><p><input type="checkbox" disabled="" checked="" />
+checked</p></li>
+</ul>
+```
+
+latex task list test:
+
+```
+% pandoc -t latex
+- [ ] foo bar
+
+ baz
+
+- [x] ok
+^D
+\begin{itemize}
+\item[$\square$]
+ foo bar
+
+ baz
+\item[$\boxtimes$]
+ ok
+\end{itemize}
+```
+
+round trip:
+
+```
+% pandoc -f markdown -t markdown
+- [ ] foo
+- [x] bar
+^D
+- [ ] foo
+- [x] bar
+```
diff --git a/test/dokuwiki_external_images.dokuwiki b/test/dokuwiki_external_images.dokuwiki
index cc7eddcda..c835fa05b 100644
--- a/test/dokuwiki_external_images.dokuwiki
+++ b/test/dokuwiki_external_images.dokuwiki
@@ -1 +1 @@
-{{https://cooluri.com/image.png|HTTPS image}} {{http://cooluri.com/image.png|HTTP image}} {{ftp://ftp.cooluri.com/image.png|FTP image}} {{file:///tmp/coolimage.png|Filesystem image}} {{:/image.jpg|Relative image 1}} {{:image.jpg|Relative image 2}}
+{{https://cooluri.com/image.png|HTTPS image}} {{http://cooluri.com/image.png|HTTP image}} {{ftp://ftp.cooluri.com/image.png|FTP image}} {{file:///tmp/coolimage.png|Filesystem image}} {{/image.jpg|Relative image 1}} {{image.jpg|Relative image 2}}
diff --git a/test/writer.dokuwiki b/test/writer.dokuwiki
index 4ba1b7054..34f4246db 100644
--- a/test/writer.dokuwiki
+++ b/test/writer.dokuwiki
@@ -609,9 +609,9 @@ or here: <http://example.com/>
From “Voyage dans la Lune” by Georges Melies (1902):
-{{:lalune.jpg|Voyage dans la Lune lalune}}
+{{lalune.jpg|Voyage dans la Lune lalune}}
-Here is a movie {{:movie.jpg|movie}} icon.
+Here is a movie {{movie.jpg|movie}} icon.
----
diff --git a/test/writer.zimwiki b/test/writer.zimwiki
index 7783b836c..4b384fb20 100644
--- a/test/writer.zimwiki
+++ b/test/writer.zimwiki
@@ -593,9 +593,9 @@ or here: <http://example.com/>
From “Voyage dans la Lune” by Georges Melies (1902):
-{{:lalune.jpg|Voyage dans la Lune lalune}}
+{{lalune.jpg|Voyage dans la Lune lalune}}
-Here is a movie {{:movie.jpg|movie}} icon.
+Here is a movie {{movie.jpg|movie}} icon.
----