aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Readers/Org/Blocks.hs
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/Pandoc/Readers/Org/Blocks.hs
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/Pandoc/Readers/Org/Blocks.hs')
-rw-r--r--src/Text/Pandoc/Readers/Org/Blocks.hs41
1 files changed, 39 insertions, 2 deletions
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.