aboutsummaryrefslogtreecommitdiff
path: root/test/Tests/Writers/Org.hs
diff options
context:
space:
mode:
Diffstat (limited to 'test/Tests/Writers/Org.hs')
-rw-r--r--test/Tests/Writers/Org.hs59
1 files changed, 46 insertions, 13 deletions
diff --git a/test/Tests/Writers/Org.hs b/test/Tests/Writers/Org.hs
index c99f7344d..bd6c9b7ab 100644
--- a/test/Tests/Writers/Org.hs
+++ b/test/Tests/Writers/Org.hs
@@ -1,8 +1,7 @@
-{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
module Tests.Writers.Org (tests) where
-import Prelude
+import Data.Text as T
import Test.Tasty
import Tests.Helpers
import Text.Pandoc
@@ -11,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"
]
- ]
+ ]
+ ]