Org reader: respect unnumbered header property
Sections the `unnumbered` property should, as the name implies, be excluded from the automatic numbering of section provided by some output formats. The Pandoc convention for this is to add an "unnumbered" class to the header. The reader treats properties as key-value pairs per default, so a special case is added to translate the above property to a class instead. Closes #3095.
This commit is contained in:
parent
abc4bca46b
commit
21cd76c201
2 changed files with 19 additions and 2 deletions
|
@ -80,6 +80,10 @@ newtype PropertyValue = PropertyValue { fromValue :: String }
|
|||
toPropertyValue :: String -> PropertyValue
|
||||
toPropertyValue = PropertyValue
|
||||
|
||||
-- | Check whether the property value is non-nil (i.e. truish).
|
||||
isNonNil :: PropertyValue -> Bool
|
||||
isNonNil p = map toLower (fromValue p) `notElem` ["()", "{}", "nil"]
|
||||
|
||||
-- | Key/value pairs from a PROPERTIES drawer
|
||||
type Properties = [(PropertyKey, PropertyValue)]
|
||||
|
||||
|
@ -200,12 +204,16 @@ propertiesToAttr properties =
|
|||
toStringPair prop = (fromKey (fst prop), fromValue (snd prop))
|
||||
customIdKey = toPropertyKey "custom_id"
|
||||
classKey = toPropertyKey "class"
|
||||
unnumberedKey = toPropertyKey "unnumbered"
|
||||
specialProperties = [customIdKey, classKey, unnumberedKey]
|
||||
id' = fromMaybe mempty . fmap fromValue . lookup customIdKey $ properties
|
||||
cls = fromMaybe mempty . fmap fromValue . lookup classKey $ properties
|
||||
kvs' = map toStringPair . filter ((`notElem` [customIdKey, classKey]) . fst)
|
||||
kvs' = map toStringPair . filter ((`notElem` specialProperties) . fst)
|
||||
$ properties
|
||||
isUnnumbered =
|
||||
fromMaybe False . fmap isNonNil . lookup unnumberedKey $ properties
|
||||
in
|
||||
(id', words cls, kvs')
|
||||
(id', words cls ++ (if isUnnumbered then ["unnumbered"] else []), kvs')
|
||||
|
||||
tagTitle :: Inlines -> [Tag] -> Inlines
|
||||
tagTitle title tags = title <> (mconcat $ map tagToInline tags)
|
||||
|
|
|
@ -818,6 +818,15 @@ tests =
|
|||
] =?>
|
||||
headerWith ("fubar", [], [("bar", "baz")]) 1 "foo"
|
||||
|
||||
|
||||
, "Headers marked with a unnumbered property get a class of the same name" =:
|
||||
unlines [ "* Not numbered"
|
||||
, " :PROPERTIES:"
|
||||
, " :UNNUMBERED: t"
|
||||
, " :END:"
|
||||
] =?>
|
||||
headerWith ("not-numbered", ["unnumbered"], []) 1 "Not numbered"
|
||||
|
||||
, "Paragraph starting with an asterisk" =:
|
||||
"*five" =?>
|
||||
para "*five"
|
||||
|
|
Loading…
Add table
Reference in a new issue