Jira writer: improve div/panel handling

Include div attributes in panels, always render divs with class `panel`
as panels, and avoid nesting of panels.
This commit is contained in:
Albert Krewinkel 2021-03-13 12:10:02 +01:00
parent 894ed8ebb0
commit a8aa301428
No known key found for this signature in database
GPG key ID: 388DC0B21F631124
2 changed files with 58 additions and 11 deletions

View file

@ -39,11 +39,17 @@ writeJira :: PandocMonad m => WriterOptions -> Pandoc -> m Text
writeJira opts = runDefaultConverter (writerWrapText opts) (pandocToJira opts)
-- | State to keep track of footnotes.
newtype ConverterState = ConverterState { stNotes :: [Text] }
data ConverterState = ConverterState
{ stNotes :: [Text] -- ^ Footnotes to be appended to the end of the text
, stInPanel :: Bool -- ^ whether we are in a @{panel}@ block
}
-- | Initial converter state.
startState :: ConverterState
startState = ConverterState { stNotes = [] }
startState = ConverterState
{ stNotes = []
, stInPanel = False
}
-- | Converter monad
type JiraConverter m = ReaderT WrapOption (StateT ConverterState m)
@ -126,14 +132,20 @@ toJiraCode :: PandocMonad m
-> Text
-> JiraConverter m [Jira.Block]
toJiraCode (ident, classes, _attribs) code = do
let addAnchor b = if T.null ident
then b
else [Jira.Para (singleton (Jira.Anchor ident))] <> b
return . addAnchor . singleton $
return . addAnchor ident . singleton $
case find (\c -> T.toLower c `elem` knownLanguages) classes of
Nothing -> Jira.NoFormat mempty code
Just l -> Jira.Code (Jira.Language l) mempty code
-- | Prepends an anchor with the given identifier.
addAnchor :: Text -> [Jira.Block] -> [Jira.Block]
addAnchor ident =
if T.null ident
then id
else \case
Jira.Para xs : bs -> (Jira.Para (Jira.Anchor ident : xs) : bs)
bs -> (Jira.Para (singleton (Jira.Anchor ident)) : bs)
-- | Creates a Jira definition list
toJiraDefinitionList :: PandocMonad m
=> [([Inline], [[Block]])]
@ -149,11 +161,16 @@ toJiraDefinitionList defItems = do
toJiraPanel :: PandocMonad m
=> Attr -> [Block]
-> JiraConverter m [Jira.Block]
toJiraPanel attr blocks = do
jiraBlocks <- toJiraBlocks blocks
return $ if attr == nullAttr
then jiraBlocks
else singleton (Jira.Panel [] jiraBlocks)
toJiraPanel (ident, classes, attribs) blocks = do
inPanel <- gets stInPanel
if inPanel || ("panel" `notElem` classes && null attribs)
then addAnchor ident <$> toJiraBlocks blocks
else do
modify $ \st -> st{ stInPanel = True }
jiraBlocks <- toJiraBlocks blocks
modify $ \st -> st{ stInPanel = inPanel }
let params = map (uncurry Jira.Parameter) attribs
return $ singleton (Jira.Panel params $ addAnchor ident jiraBlocks)
-- | Creates a Jira header
toJiraHeader :: PandocMonad m

View file

@ -79,4 +79,34 @@ tests =
"{noformat}\npreformatted\n text.\n{noformat}"
]
]
, testGroup "blocks"
[ testGroup "div"
[ "empty attributes" =:
divWith nullAttr (para "interesting text") =?>
"interesting text"
, "just identifier" =:
divWith ("a", [], []) (para "interesting text") =?>
"{anchor:a}interesting text"
, "with class 'panel'" =:
divWith ("", ["panel"], []) (para "Contents!") =?>
"{panel}\nContents\\!\n{panel}\n"
, "panel with id" =:
divWith ("b", ["panel"], []) (para "text") =?>
"{panel}\n{anchor:b}text\n{panel}\n"
, "title attribute" =:
divWith ("", [], [("title", "Gimme!")]) (para "Contents!") =?>
"{panel:title=Gimme!}\nContents\\!\n{panel}\n"
, "nested panels" =:
let panelAttr = ("", ["panel"], [])
in divWith panelAttr (para "hi" <>
divWith panelAttr (para "wassup?")) =?>
"{panel}\nhi\n\nwassup?\n{panel}\n"
]
]
]