diff options
author | Albert Krewinkel <albert@zeitkraut.de> | 2017-12-25 23:31:05 +0100 |
---|---|---|
committer | Albert Krewinkel <albert@zeitkraut.de> | 2017-12-28 14:16:04 +0100 |
commit | e5c8b650041a270b58e2f72e18eb28a32f153954 (patch) | |
tree | 14b0af0d3b6ddd7b685170debc81d1867a9ea47b /test/Tests | |
parent | 2d443ecb07491f81e35b60d9c6cdd9041ab1c4dd (diff) | |
download | pandoc-e5c8b650041a270b58e2f72e18eb28a32f153954.tar.gz |
Org reader: support minlevel option for includes
The level of headers in included files can be shifted to a higher level
by specifying a minimum header level via the `:minlevel` parameter. E.g.
`#+include: "tour.org" :minlevel 1` will shift the headers in tour.org
such that the topmost headers become level 1 headers.
Fixes: #4154
Diffstat (limited to 'test/Tests')
-rw-r--r-- | test/Tests/Readers/Org/Directive.hs | 78 |
1 files changed, 77 insertions, 1 deletions
diff --git a/test/Tests/Readers/Org/Directive.hs b/test/Tests/Readers/Org/Directive.hs index 29ffaa20c..1970a0471 100644 --- a/test/Tests/Readers/Org/Directive.hs +++ b/test/Tests/Readers/Org/Directive.hs @@ -1,13 +1,42 @@ {-# LANGUAGE OverloadedStrings #-} module Tests.Readers.Org.Directive (tests) where +import Control.Arrow (second) +import Data.Time (UTCTime (UTCTime), secondsToDiffTime) +import Data.Time.Calendar (Day (ModifiedJulianDay)) import Test.Tasty (TestTree, testGroup) -import Tests.Helpers ((=?>)) +import Tests.Helpers ((=?>), ToString, purely, test) import Tests.Readers.Org.Shared ((=:), tagSpan) import Text.Pandoc import Text.Pandoc.Builder +import qualified Data.ByteString as BS +import qualified Data.Map as Map import qualified Data.Text as T +testWithFiles :: (ToString c) + => [(FilePath, BS.ByteString)] + -> String -- ^ name of test case + -> (T.Text, c) -- ^ (input, expected value) + -> TestTree +testWithFiles fileDefs = test (orgWithFiles fileDefs) + where +orgWithFiles :: [(FilePath, BS.ByteString)] -> T.Text -> Pandoc +orgWithFiles fileDefs input = + let readOrg' = readOrg def{ readerExtensions = getDefaultExtensions "org" } + in flip purely input $ \inp -> do + modifyPureState (\st -> st { stFiles = files fileDefs }) + readOrg' inp + + +files :: [(FilePath, BS.ByteString)] -> FileTree +files fileDefs = + let dummyTime = UTCTime (ModifiedJulianDay 125) (secondsToDiffTime 0) + fileInfo content = FileInfo + { infoFileMTime = dummyTime + , infoFileContents = content + } + in FileTree (Map.fromList (map (second fileInfo) fileDefs)) + tests :: [TestTree] tests = [ testGroup "export options" @@ -125,4 +154,51 @@ tests = ] =?> headerWith ("headline", [], mempty) 1 "Headline" ] + + , testGroup "Include" + [ testWithFiles [("./other.org", "content of other file\n")] + "file inclusion" + (T.unlines [ "#+include: \"other.org\"" ] =?> + plain "content of other file") + + , testWithFiles [("./world.org", "World\n\n")] + "Included file belongs to item" + (T.unlines [ "- Hello,\n #+include: \"world.org\"" ] =?> + bulletList [para "Hello," <> para "World"]) + + , testWithFiles [("./level3.org", "*** Level3\n\n")] + "Default include preserves level" + (T.unlines [ "#+include: \"level3.org\"" ] =?> + headerWith ("level3", [], []) 3 "Level3") + + , testWithFiles [("./level3.org", "*** Level3\n\n")] + "Minlevel shifts level" + (T.unlines [ "#+include: \"level3.org\" :minlevel 1" ] =?> + headerWith ("level3", [], []) 1 "Level3") + + , testWithFiles [("./src.hs", "putStrLn outString\n")] + "Include file as source code snippet" + (T.unlines [ "#+include: \"src.hs\" src haskell" ] =?> + codeBlockWith ("", ["haskell"], []) "putStrLn outString\n") + + , testWithFiles [("./export-latex.org", "\\emph{Hello}\n")] + "Include file as export snippet" + (T.unlines [ "#+include: \"export-latex.org\" export latex" ] =?> + rawBlock "latex" "\\emph{Hello}\n") + + , testWithFiles [("./subdir/foo-bar.latex", "foo\n"), + ("./hello.lisp", "(print \"Hello!\")\n") + ] + "include directive is limited to one line" + (T.unlines [ "#+INCLUDE: \"hello.lisp\" src lisp" + , "#+include: \"subdir/foo-bar.latex\" export latex" + , "bar" + ] =?> + mconcat + [ codeBlockWith ("", ["lisp"], []) "(print \"Hello!\")\n" + , rawBlock "latex" "foo\n" + , para "bar" + ] + ) + ] ] |