Org reader: fix behavior for successive calls of #+EXCLUDE_TAGS
. (#4951)
Calling `#+EXCLUDE_TAGS` multiple times should preserve the status of the previously declared tags.
This commit is contained in:
parent
6207bdeb68
commit
e257b54124
3 changed files with 23 additions and 7 deletions
|
@ -159,7 +159,7 @@ optionLine = try $ do
|
|||
"seq_todo" -> todoSequence >>= updateState . registerTodoSequence
|
||||
"typ_todo" -> todoSequence >>= updateState . registerTodoSequence
|
||||
"macro" -> macroDefinition >>= updateState . registerMacro
|
||||
"exclude_tags" -> excludedTagSet >>= updateState . setExcludedTags
|
||||
"exclude_tags" -> excludedTagList >>= updateState . setExcludedTags
|
||||
"pandoc-emphasis-pre" -> emphChars >>= updateState . setEmphasisPreChar
|
||||
"pandoc-emphasis-post" -> emphChars >>= updateState . setEmphasisPostChar
|
||||
_ -> mzero
|
||||
|
@ -192,14 +192,17 @@ parseFormat = try $ replacePlain <|> replaceUrl <|> justAppend
|
|||
rest = manyTill anyChar (eof <|> () <$ oneOf "\n\r")
|
||||
tillSpecifier c = manyTill (noneOf "\n\r") (try $ string ('%':c:""))
|
||||
|
||||
excludedTagSet :: Monad m => OrgParser m (Set.Set Tag)
|
||||
excludedTagSet = do
|
||||
excludedTagList :: Monad m => OrgParser m [Tag]
|
||||
excludedTagList = do
|
||||
skipSpaces
|
||||
Set.fromList . map Tag <$>
|
||||
many (orgTagWord <* skipSpaces) <* newline
|
||||
map Tag <$> many (orgTagWord <* skipSpaces) <* newline
|
||||
|
||||
setExcludedTags :: Set.Set Tag -> OrgParserState -> OrgParserState
|
||||
setExcludedTags tagSet st = st { orgStateExcludedTags = tagSet }
|
||||
setExcludedTags :: [Tag] -> OrgParserState -> OrgParserState
|
||||
setExcludedTags tagList st =
|
||||
let finalSet = if orgStateExcludedTagsChanged st
|
||||
then foldr Set.insert (orgStateExcludedTags st) tagList
|
||||
else Set.fromList tagList
|
||||
in st { orgStateExcludedTags = finalSet, orgStateExcludedTagsChanged = True}
|
||||
|
||||
setEmphasisPreChar :: Maybe [Char] -> OrgParserState -> OrgParserState
|
||||
setEmphasisPreChar csMb st =
|
||||
|
|
|
@ -118,6 +118,7 @@ data OrgParserState = OrgParserState
|
|||
, orgStateEmphasisPostChars :: [Char] -- ^ Chars allowed at after emphasis
|
||||
, orgStateEmphasisNewlines :: Maybe Int
|
||||
, orgStateExcludedTags :: Set.Set Tag
|
||||
, orgStateExcludedTagsChanged :: Bool
|
||||
, orgStateExportSettings :: ExportSettings
|
||||
, orgStateHeaderMap :: M.Map Inlines String
|
||||
, orgStateIdentifiers :: Set.Set String
|
||||
|
@ -189,6 +190,7 @@ defaultOrgParserState = OrgParserState
|
|||
, orgStateEmphasisNewlines = Nothing
|
||||
, orgStateExportSettings = def
|
||||
, orgStateExcludedTags = Set.singleton $ Tag "noexport"
|
||||
, orgStateExcludedTagsChanged = False
|
||||
, orgStateHeaderMap = M.empty
|
||||
, orgStateIdentifiers = Set.empty
|
||||
, orgStateIncludeFiles = []
|
||||
|
|
|
@ -20,6 +20,17 @@
|
|||
[Header 1 ("this-should-appear",[],[]) [Str "This",Space,Str "should",Space,Str "appear",Space,Span ("",["tag"],[("tag-name","fawn")]) [SmallCaps [Str "fawn"]]]]
|
||||
```
|
||||
|
||||
```
|
||||
% pandoc -f org -t native
|
||||
#+EXCLUDE_TAGS: giraffe
|
||||
#+EXCLUDE_TAGS: hippo
|
||||
* This should not appear :giraffe:
|
||||
* This should not appear :hippo:
|
||||
* This should appear :noexport:
|
||||
^D
|
||||
[Header 1 ("this-should-appear",[],[]) [Str "This",Space,Str "should",Space,Str "appear",Space,Span ("",["tag"],[("tag-name","noexport")]) [SmallCaps [Str "noexport"]]]]
|
||||
```
|
||||
|
||||
```
|
||||
% pandoc -f org -t native
|
||||
#+EXCLUDE_TAGS:
|
||||
|
|
Loading…
Add table
Reference in a new issue