aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorleungbk <bkleung89@gmail.com>2019-01-27 04:52:00 +0100
committerAlbert Krewinkel <albert+github@zeitkraut.de>2019-01-30 18:27:38 +0100
commitdc431745730aaac244a2e59b25f5554a654abf4c (patch)
treee36296b1e14fdb6010bdb369df1618884ee49a8c
parentc9454a4176878803870c3f658ba01b5727b11776 (diff)
downloadpandoc-dc431745730aaac244a2e59b25f5554a654abf4c.tar.gz
Org reader: separate filtering logic from conversion function.
-rw-r--r--src/Text/Pandoc/Readers/Org/Blocks.hs7
-rw-r--r--src/Text/Pandoc/Readers/Org/DocumentTree.hs12
2 files changed, 11 insertions, 8 deletions
diff --git a/src/Text/Pandoc/Readers/Org/Blocks.hs b/src/Text/Pandoc/Readers/Org/Blocks.hs
index 9e3fe3d79..d6930398c 100644
--- a/src/Text/Pandoc/Readers/Org/Blocks.hs
+++ b/src/Text/Pandoc/Readers/Org/Blocks.hs
@@ -34,7 +34,7 @@ module Text.Pandoc.Readers.Org.Blocks
import Prelude
import Text.Pandoc.Readers.Org.BlockStarts
-import Text.Pandoc.Readers.Org.DocumentTree (documentTree, headlineToBlocks)
+import Text.Pandoc.Readers.Org.DocumentTree (documentTree, headlineToBlocks, filterHeadlineTree)
import Text.Pandoc.Readers.Org.Inlines
import Text.Pandoc.Readers.Org.Meta (metaExport, metaKey, metaLine)
import Text.Pandoc.Readers.Org.ParserState
@@ -64,9 +64,10 @@ import qualified Text.Pandoc.Walk as Walk
-- | Get a list of blocks.
blockList :: PandocMonad m => OrgParser m [Block]
blockList = do
- headlines <- documentTree blocks inline
+ fHeadlineTree <- documentTree blocks inline
st <- getState
- headlineBlocks <- headlineToBlocks $ runF headlines st
+ let headlineTree = runF fHeadlineTree st
+ headlineBlocks <- headlineToBlocks $ filterHeadlineTree headlineTree st
-- ignore first headline, it's the document's title
return . drop 1 . B.toList $ headlineBlocks
diff --git a/src/Text/Pandoc/Readers/Org/DocumentTree.hs b/src/Text/Pandoc/Readers/Org/DocumentTree.hs
index 7d55892fe..131408289 100644
--- a/src/Text/Pandoc/Readers/Org/DocumentTree.hs
+++ b/src/Text/Pandoc/Readers/Org/DocumentTree.hs
@@ -29,6 +29,7 @@ Parsers for org-mode headlines and document subtrees
module Text.Pandoc.Readers.Org.DocumentTree
( documentTree
, headlineToBlocks
+ , filterHeadlineTree
) where
import Prelude
@@ -161,17 +162,18 @@ headlineToBlocks hdln = do
let tags = headlineTags hdln
let text = headlineText hdln
let level = headlineLevel hdln
- shouldNotExport <- hasDoNotExportTag tags
case () of
- _ | shouldNotExport -> return mempty
_ | any isArchiveTag tags -> archivedHeadlineToBlocks hdln
_ | isCommentTitle text -> return mempty
_ | maxLevel <= level -> headlineToHeaderWithList hdln
_ | otherwise -> headlineToHeaderWithContents hdln
-hasDoNotExportTag :: Monad m => [Tag] -> OrgParser m Bool
-hasDoNotExportTag tags = containsExcludedTag . orgStateExcludedTags <$> getState
- where containsExcludedTag s = any (`Set.member` s) tags
+filterHeadlineTree :: Headline -> OrgParserState -> Headline
+filterHeadlineTree hdln st =
+ hdln { headlineChildren =
+ [filterHeadlineTree childHdln st |
+ childHdln <- headlineChildren hdln,
+ not $ any (`Set.member` orgStateExcludedTags st) (headlineTags childHdln)] }
isArchiveTag :: Tag -> Bool
isArchiveTag = (== toTag "ARCHIVE")