aboutsummaryrefslogtreecommitdiff
path: root/test
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 /test
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 'test')
-rw-r--r--test/Tests/Readers/Org/Block/List.hs13
-rw-r--r--test/Tests/Writers/Org.hs57
2 files changed, 59 insertions, 11 deletions
diff --git a/test/Tests/Readers/Org/Block/List.hs b/test/Tests/Readers/Org/Block/List.hs
index 9686b5148..2ee37081e 100644
--- a/test/Tests/Readers/Org/Block/List.hs
+++ b/test/Tests/Readers/Org/Block/List.hs
@@ -118,6 +118,19 @@ tests =
] =?>
bulletList [ plain "", plain "" ]
+ , "Task list" =:
+ T.unlines [ "- [ ] nope"
+ , "- [X] yup"
+ , "- [-] started"
+ , " 1. [X] sure"
+ , " 2. [ ] nuh-uh"
+ ] =?>
+ bulletList [ plain "☐ nope", plain "☒ yup"
+ , mconcat [ plain "☐ started"
+ , orderedList [plain "☒ sure", plain "☐ nuh-uh"]
+ ]
+ ]
+
, "Simple Ordered List" =:
("1. Item1\n" <>
"2. Item2\n") =?>
diff --git a/test/Tests/Writers/Org.hs b/test/Tests/Writers/Org.hs
index 9cbe360da..bd6c9b7ab 100644
--- a/test/Tests/Writers/Org.hs
+++ b/test/Tests/Writers/Org.hs
@@ -1,6 +1,7 @@
{-# LANGUAGE OverloadedStrings #-}
module Tests.Writers.Org (tests) where
+import Data.Text as T
import Test.Tasty
import Tests.Helpers
import Text.Pandoc
@@ -9,17 +10,51 @@ import Text.Pandoc.Builder
infix 4 =:
(=:) :: (ToString a, ToPandoc a)
- => String -> (a, String) -> TestTree
-(=:) = test (purely (writeOrg def . toPandoc))
+ => String -> (a, Text) -> TestTree
+(=:) = test org
+
+defopts :: WriterOptions
+defopts = def
+ { writerExtensions = getDefaultExtensions "org"
+ }
+
+org :: (ToPandoc a) => a -> Text
+org = orgWithOpts defopts
+
+orgWithOpts :: (ToPandoc a) => WriterOptions -> a -> Text
+orgWithOpts opts x = purely (writeOrg opts) $ toPandoc x
+
tests :: [TestTree]
-tests = [ testGroup "links"
- -- See http://orgmode.org/manual/Internal-links.html#Internal-links
- [ "simple link"
- =: link "/url" "" "foo"
- =?> "[[/url][foo]]"
- , "internal link to anchor"
- =: link "#my-custom-id" "" "#my-custom-id"
- =?> "[[#my-custom-id]]"
+tests =
+ [ testGroup "links"
+ -- See http://orgmode.org/manual/Internal-links.html#Internal-links
+ [ "simple link"
+ =: link "/url" "" "foo"
+ =?> "[[/url][foo]]"
+ , "internal link to anchor"
+ =: link "#my-custom-id" "" "#my-custom-id"
+ =?> "[[#my-custom-id]]"
+ ]
+
+ , testGroup "lists"
+ [ "bullet task list"
+ =: bulletList [plain "☐ a", plain "☒ b"]
+ =?> T.unlines
+ [ "- [ ] a"
+ , "- [X] b"
+ ]
+ , "ordered task list"
+ =: orderedList [plain ("☐" <> space <> "a"), plain "☒ b"]
+ =?> T.unlines
+ [ "1. [ ] a"
+ , "2. [X] b"
+ ]
+ , test (orgWithOpts def) "bullet without task_lists" $
+ bulletList [plain "☐ a", plain "☒ b"]
+ =?> T.unlines
+ [ "- ☐ a"
+ , "- ☒ b"
]
- ]
+ ]
+ ]