aboutsummaryrefslogtreecommitdiff
path: root/src/Text
diff options
context:
space:
mode:
authorAlbert Krewinkel <albert@zeitkraut.de>2021-02-13 09:37:43 +0100
committerJohn MacFarlane <jgm@berkeley.edu>2021-02-13 13:00:37 -0800
commita3beed9db874517fa57b55380658f4e019e809b2 (patch)
tree7575848ae45ecb795a4a8fc2187a9a4db959d8b7 /src/Text
parent2d60a5127cc28bb6b55c19309d6e8fb6e81fbe66 (diff)
downloadpandoc-a3beed9db874517fa57b55380658f4e019e809b2.tar.gz
Org: support task_lists extension
The tasks lists extension is now supported by the org reader and writer; the extension is turned on by default. Closes: #6336
Diffstat (limited to 'src/Text')
-rw-r--r--src/Text/Pandoc/Extensions.hs2
-rw-r--r--src/Text/Pandoc/Readers/Org/Blocks.hs41
-rw-r--r--src/Text/Pandoc/Writers/Org.hs16
3 files changed, 54 insertions, 5 deletions
diff --git a/src/Text/Pandoc/Extensions.hs b/src/Text/Pandoc/Extensions.hs
index 82eb0e957..3b96f9e04 100644
--- a/src/Text/Pandoc/Extensions.hs
+++ b/src/Text/Pandoc/Extensions.hs
@@ -381,6 +381,7 @@ getDefaultExtensions "commonmark_x" = extensionsFromList
]
getDefaultExtensions "org" = extensionsFromList
[Ext_citations,
+ Ext_task_lists,
Ext_auto_identifiers]
getDefaultExtensions "html" = extensionsFromList
[Ext_auto_identifiers,
@@ -515,6 +516,7 @@ getAllExtensions f = universalExtensions <> getAll f
extensionsFromList
[ Ext_citations
, Ext_smart
+ , Ext_task_lists
]
getAll "html" = autoIdExtensions <>
extensionsFromList
diff --git a/src/Text/Pandoc/Readers/Org/Blocks.hs b/src/Text/Pandoc/Readers/Org/Blocks.hs
index 6bd046e04..d1aff701e 100644
--- a/src/Text/Pandoc/Readers/Org/Blocks.hs
+++ b/src/Text/Pandoc/Readers/Org/Blocks.hs
@@ -1,6 +1,7 @@
{-# LANGUAGE FlexibleContexts #-}
-{-# LANGUAGE RecordWildCards #-}
+{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
+{-# LANGUAGE RecordWildCards #-}
{- |
Module : Text.Pandoc.Readers.Org.Blocks
Copyright : Copyright (C) 2014-2021 Albert Krewinkel
@@ -850,16 +851,52 @@ definitionListItem parseIndentedMarker = try $ do
definitionMarker =
spaceChar *> string "::" <* (spaceChar <|> lookAhead newline)
+-- | Checkbox for tasks.
+data Checkbox
+ = UncheckedBox
+ | CheckedBox
+ | SemicheckedBox
+
+-- | Parses a checkbox in a plain list.
+checkbox :: PandocMonad m
+ => OrgParser m Checkbox
+checkbox = do
+ guardEnabled Ext_task_lists
+ try (char '[' *> status <* char ']') <?> "checkbox"
+ where
+ status = choice
+ [ UncheckedBox <$ char ' '
+ , CheckedBox <$ char 'X'
+ , SemicheckedBox <$ char '-'
+ ]
+
+checkboxToInlines :: Checkbox -> Inline
+checkboxToInlines = B.Str . \case
+ UncheckedBox -> "☐"
+ SemicheckedBox -> "☐"
+ CheckedBox -> "☒"
+
-- | parse raw text for one list item
listItem :: PandocMonad m
=> OrgParser m Int
-> OrgParser m (F Blocks)
listItem parseIndentedMarker = try . withContext ListItemState $ do
markerLength <- try parseIndentedMarker
+ box <- optionMaybe checkbox
firstLine <- anyLineNewline
blank <- option "" ("\n" <$ blankline)
rest <- T.concat <$> many (listContinuation markerLength)
- parseFromString blocks $ firstLine <> blank <> rest
+ contents <- parseFromString blocks $ firstLine <> blank <> rest
+ return (maybe id (prependInlines . checkboxToInlines) box <$> contents)
+
+-- | Prepend inlines to blocks, adding them to the first paragraph or
+-- creating a new Plain element if necessary.
+prependInlines :: Inline -> Blocks -> Blocks
+prependInlines inlns = B.fromList . prepend . B.toList
+ where
+ prepend (Plain is : bs) = Plain (inlns : Space : is) : bs
+ prepend (Para is : bs) = Para (inlns : Space : is) : bs
+ prepend bs = Plain [inlns, Space] : bs
-- continuation of a list item - indented and separated by blankline or endline.
-- Note: nested lists are parsed as continuations.
diff --git a/src/Text/Pandoc/Writers/Org.hs b/src/Text/Pandoc/Writers/Org.hs
index 43ebf1807..8dfc2749c 100644
--- a/src/Text/Pandoc/Writers/Org.hs
+++ b/src/Text/Pandoc/Writers/Org.hs
@@ -213,25 +213,35 @@ blockToOrg (DefinitionList items) = do
-- | Convert bullet list item (list of blocks) to Org.
bulletListItemToOrg :: PandocMonad m => [Block] -> Org m (Doc Text)
bulletListItemToOrg items = do
- contents <- blockListToOrg items
+ exts <- gets $ writerExtensions . stOptions
+ contents <- blockListToOrg (taskListItemToOrg exts items)
return $ hang 2 "- " contents $$
if endsWithPlain items
then cr
else blankline
-
-- | Convert ordered list item (a list of blocks) to Org.
orderedListItemToOrg :: PandocMonad m
=> Text -- ^ marker for list item
-> [Block] -- ^ list item (list of blocks)
-> Org m (Doc Text)
orderedListItemToOrg marker items = do
- contents <- blockListToOrg items
+ exts <- gets $ writerExtensions . stOptions
+ contents <- blockListToOrg (taskListItemToOrg exts items)
return $ hang (T.length marker + 1) (literal marker <> space) contents $$
if endsWithPlain items
then cr
else blankline
+-- | Convert a list item containing text starting with @U+2610 BALLOT BOX@
+-- or @U+2612 BALLOT BOX WITH X@ to org checkbox syntax (e.g. @[X]@).
+taskListItemToOrg :: Extensions -> [Block] -> [Block]
+taskListItemToOrg = handleTaskListItem toOrg
+ where
+ toOrg (Str "☐" : Space : is) = Str "[ ]" : Space : is
+ toOrg (Str "☒" : Space : is) = Str "[X]" : Space : is
+ toOrg is = is
+
-- | Convert definition list item (label, list of blocks) to Org.
definitionListItemToOrg :: PandocMonad m
=> ([Inline], [[Block]]) -> Org m (Doc Text)