Org reader: respect export option p
for planning info
Inclusion of planning info (*DEADLINE*, *SCHEDULED*, and *CLOSED*) can be controlled via the `p` export option: setting the option to `t` will add all planning information in a *Plain* block below the respective headline.
This commit is contained in:
parent
aac3d752e1
commit
275afec38a
5 changed files with 64 additions and 2 deletions
|
@ -204,6 +204,7 @@ headlineToHeaderWithList hdln = do
|
|||
maxHeadlineLevels <- getExportSetting exportHeadlineLevels
|
||||
header <- headlineToHeader hdln
|
||||
listElements <- mapM headlineToBlocks (headlineChildren hdln)
|
||||
planningBlock <- planningToBlock (headlinePlanning hdln)
|
||||
let listBlock = if null listElements
|
||||
then mempty
|
||||
else B.orderedList listElements
|
||||
|
@ -213,6 +214,7 @@ headlineToHeaderWithList hdln = do
|
|||
return . mconcat $
|
||||
[ headerText
|
||||
, headlineContents hdln
|
||||
, planningBlock
|
||||
, listBlock
|
||||
]
|
||||
where
|
||||
|
@ -225,8 +227,9 @@ headlineToHeaderWithList hdln = do
|
|||
headlineToHeaderWithContents :: Monad m => Headline -> OrgParser m Blocks
|
||||
headlineToHeaderWithContents hdln = do
|
||||
header <- headlineToHeader hdln
|
||||
planningBlock <- planningToBlock (headlinePlanning hdln)
|
||||
childrenBlocks <- mconcat <$> mapM headlineToBlocks (headlineChildren hdln)
|
||||
return $ header <> headlineContents hdln <> childrenBlocks
|
||||
return $ header <> planningBlock <> headlineContents hdln <> childrenBlocks
|
||||
|
||||
headlineToHeader :: Monad m => Headline -> OrgParser m Blocks
|
||||
headlineToHeader hdln = do
|
||||
|
@ -287,6 +290,27 @@ tagsToInlines tags =
|
|||
tagSpan :: Tag -> Inlines -> Inlines
|
||||
tagSpan t = B.spanWith ("", ["tag"], [("tag-name", fromTag t)])
|
||||
|
||||
-- | Render planning info as a block iff the respective export setting is
|
||||
-- enabled.
|
||||
planningToBlock :: Monad m => PlanningInfo -> OrgParser m Blocks
|
||||
planningToBlock planning = do
|
||||
includePlanning <- getExportSetting exportWithPlanning
|
||||
return $
|
||||
if includePlanning
|
||||
then B.plain . mconcat . intersperse B.space . filter (/= mempty) $
|
||||
[ datumInlines planningClosed "CLOSED"
|
||||
, datumInlines planningDeadline "DEADLINE"
|
||||
, datumInlines planningScheduled "SCHEDULED"
|
||||
]
|
||||
else mempty
|
||||
where
|
||||
datumInlines field name =
|
||||
case field planning of
|
||||
Nothing -> mempty
|
||||
Just time -> B.strong (B.str name <> B.str ":")
|
||||
<> B.space
|
||||
<> B.emph (B.str time)
|
||||
|
||||
-- | An Org timestamp, including repetition marks. TODO: improve
|
||||
type Timestamp = String
|
||||
|
||||
|
|
|
@ -69,7 +69,7 @@ exportSetting = choice
|
|||
, integerSetting "H" (\val es -> es { exportHeadlineLevels = val })
|
||||
, ignoredSetting "inline"
|
||||
, ignoredSetting "num"
|
||||
, ignoredSetting "p"
|
||||
, booleanSetting "p" (\val es -> es { exportWithPlanning = val })
|
||||
, ignoredSetting "pri"
|
||||
, ignoredSetting "prop"
|
||||
, ignoredSetting "stat"
|
||||
|
|
|
@ -260,6 +260,7 @@ data ExportSettings = ExportSettings
|
|||
, exportWithAuthor :: Bool -- ^ Include author in final meta-data
|
||||
, exportWithCreator :: Bool -- ^ Include creator in final meta-data
|
||||
, exportWithEmail :: Bool -- ^ Include email in final meta-data
|
||||
, exportWithPlanning :: Bool -- ^ Keep planning info after headlines
|
||||
, exportWithTags :: Bool -- ^ Keep tags as part of headlines
|
||||
, exportWithTodoKeywords :: Bool -- ^ Keep TODO keywords in headers
|
||||
}
|
||||
|
@ -280,6 +281,7 @@ defaultExportSettings = ExportSettings
|
|||
, exportWithAuthor = True
|
||||
, exportWithCreator = True
|
||||
, exportWithEmail = True
|
||||
, exportWithPlanning = False
|
||||
, exportWithTags = True
|
||||
, exportWithTodoKeywords = True
|
||||
}
|
||||
|
|
|
@ -205,5 +205,18 @@ tests =
|
|||
, " :END:"
|
||||
] =?>
|
||||
headerWith ("look", [], []) 1 "important"
|
||||
|
||||
, "Planning info followed by test" =:
|
||||
T.unlines [ "* important "
|
||||
, " " <> T.unwords
|
||||
[ "CLOSED: [2018-09-05 Wed 13:58]"
|
||||
, "DEADLINE: <2018-09-17 Mon>"
|
||||
, "SCHEDULED: <2018-09-10 Mon>"
|
||||
]
|
||||
, " :PROPERTIES:"
|
||||
, " :custom_id: look"
|
||||
, " :END:"
|
||||
] =?>
|
||||
headerWith ("look", [], []) 1 "important"
|
||||
]
|
||||
]
|
||||
|
|
|
@ -150,6 +150,29 @@ tests =
|
|||
, "* Headline :hello:world:"
|
||||
] =?>
|
||||
headerWith ("headline", [], mempty) 1 "Headline"
|
||||
|
||||
, testGroup "planning information"
|
||||
[ "include planning info after headlines" =:
|
||||
T.unlines [ "#+OPTIONS: p:t"
|
||||
, "* important"
|
||||
, " DEADLINE: <2018-10-01 Mon> SCHEDULED: <2018-09-15 Sat>"
|
||||
] =?>
|
||||
mconcat [ headerWith ("important", mempty, mempty) 1 "important"
|
||||
, plain $ strong "DEADLINE:"
|
||||
<> space
|
||||
<> emph (str "<2018-10-01 Mon>")
|
||||
<> space
|
||||
<> strong "SCHEDULED:"
|
||||
<> space
|
||||
<> emph (str "<2018-09-15 Sat>")
|
||||
]
|
||||
|
||||
, "empty planning info is not included" =:
|
||||
T.unlines [ "#+OPTIONS: p:t"
|
||||
, "* Wichtig"
|
||||
] =?>
|
||||
headerWith ("wichtig", mempty, mempty) 1 "Wichtig"
|
||||
]
|
||||
]
|
||||
|
||||
, testGroup "Include"
|
||||
|
|
Loading…
Add table
Reference in a new issue