Org reader: respect author
export option
The `author` option controls whether the author should be included in the final markup. Setting `#+OPTIONS: author:nil` will drop the author from the final meta-data output.
This commit is contained in:
parent
ad625782b1
commit
117d3f4d92
5 changed files with 29 additions and 4 deletions
|
@ -35,7 +35,7 @@ module Text.Pandoc.Readers.Org.Blocks
|
|||
|
||||
import Text.Pandoc.Readers.Org.BlockStarts
|
||||
import Text.Pandoc.Readers.Org.Inlines
|
||||
import Text.Pandoc.Readers.Org.Meta ( metaLine )
|
||||
import Text.Pandoc.Readers.Org.Meta ( metaExport, metaLine )
|
||||
import Text.Pandoc.Readers.Org.ParserState
|
||||
import Text.Pandoc.Readers.Org.Parsing
|
||||
import Text.Pandoc.Readers.Org.Shared
|
||||
|
@ -230,8 +230,8 @@ blockList = do
|
|||
-- | Get the meta information safed in the state.
|
||||
meta :: OrgParser Meta
|
||||
meta = do
|
||||
st <- getState
|
||||
return $ runF (orgStateMeta st) st
|
||||
meta' <- metaExport
|
||||
runF meta' <$> getState
|
||||
|
||||
blocks :: OrgParser (F Blocks)
|
||||
blocks = mconcat <$> manyTill block (void (lookAhead headerStart) <|> eof)
|
||||
|
|
|
@ -54,7 +54,7 @@ exportSetting = choice
|
|||
, ignoredSetting "<"
|
||||
, ignoredSetting "\\n"
|
||||
, archivedTreeSetting "arch" (\val es -> es { exportArchivedTrees = val })
|
||||
, ignoredSetting "author"
|
||||
, booleanSetting "author" (\val es -> es { exportWithAuthor = val })
|
||||
, ignoredSetting "c"
|
||||
, ignoredSetting "creator"
|
||||
, complementableListSetting "d" (\val es -> es { exportDrawers = val })
|
||||
|
|
|
@ -29,6 +29,7 @@ Parsers for Org-mode meta declarations.
|
|||
-}
|
||||
module Text.Pandoc.Readers.Org.Meta
|
||||
( metaLine
|
||||
, metaExport
|
||||
) where
|
||||
|
||||
import Text.Pandoc.Readers.Org.BlockStarts
|
||||
|
@ -48,6 +49,22 @@ import Data.List ( intersperse )
|
|||
import qualified Data.Map as M
|
||||
import Network.HTTP ( urlEncode )
|
||||
|
||||
-- | Returns the current meta, respecting export options.
|
||||
metaExport :: OrgParser (F Meta)
|
||||
metaExport = do
|
||||
st <- getState
|
||||
let withAuthor = extractExportOption exportWithAuthor st
|
||||
return $ (if withAuthor then id else removeMeta "author")
|
||||
<$> orgStateMeta st
|
||||
|
||||
removeMeta :: String -> Meta -> Meta
|
||||
removeMeta key meta' =
|
||||
let metaMap = unMeta meta'
|
||||
in Meta $ M.delete key metaMap
|
||||
|
||||
extractExportOption :: (ExportSettings -> a) -> OrgParserState -> a
|
||||
extractExportOption ex = ex . orgStateExportSettings
|
||||
|
||||
-- | Parse and handle a single line containing meta information
|
||||
-- The order, in which blocks are tried, makes sure that we're not looking at
|
||||
-- the beginning of a block, so we don't need to check for it
|
||||
|
|
|
@ -163,6 +163,7 @@ data ExportSettings = ExportSettings
|
|||
, exportSmartQuotes :: Bool -- ^ Parse quotes smartly
|
||||
, exportSpecialStrings :: Bool -- ^ Parse ellipses and dashes smartly
|
||||
, exportSubSuperscripts :: Bool -- ^ TeX-like syntax for sub- and superscripts
|
||||
, exportWithAuthor :: Bool -- ^ Include author in final meta-data
|
||||
}
|
||||
|
||||
instance Default ExportSettings where
|
||||
|
@ -177,6 +178,7 @@ defaultExportSettings = ExportSettings
|
|||
, exportSmartQuotes = True
|
||||
, exportSpecialStrings = True
|
||||
, exportSubSuperscripts = True
|
||||
, exportWithAuthor = True
|
||||
}
|
||||
|
||||
|
||||
|
|
|
@ -668,6 +668,12 @@ tests =
|
|||
, headerWith ("subsection", [], []) 2 "subsection"
|
||||
, orderedList [ para "list item 1", para "list item 2" ]
|
||||
]
|
||||
|
||||
, "disable author export" =:
|
||||
unlines [ "#+OPTIONS: author:nil"
|
||||
, "#+AUTHOR: ShyGuy"
|
||||
] =?>
|
||||
Pandoc nullMeta mempty
|
||||
]
|
||||
]
|
||||
|
||||
|
|
Loading…
Add table
Reference in a new issue