Markdown writer: Abstract out note/ref function.
We do basically the same thing every time we insert notes, so let's cut down on code duplication.
This commit is contained in:
parent
886e131949
commit
cd1427876e
1 changed files with 22 additions and 28 deletions
|
@ -1,4 +1,4 @@
|
||||||
{-# LANGUAGE OverloadedStrings, TupleSections, ScopedTypeVariables #-}
|
{-# LANGUAGE OverloadedStrings, TupleSections, ScopedTypeVariables, MultiWayIf #-}
|
||||||
{-
|
{-
|
||||||
Copyright (C) 2006-2015 John MacFarlane <jgm@berkeley.edu>
|
Copyright (C) 2006-2015 John MacFarlane <jgm@berkeley.edu>
|
||||||
|
|
||||||
|
@ -204,15 +204,10 @@ pandocToMarkdown opts (Pandoc meta blocks) = do
|
||||||
_ -> blocks
|
_ -> blocks
|
||||||
else blocks
|
else blocks
|
||||||
body <- blockListToMarkdown opts blocks'
|
body <- blockListToMarkdown opts blocks'
|
||||||
st <- get
|
notesAndRefs' <- notesAndRefs opts
|
||||||
notes' <- notesToMarkdown opts (reverse $ stNotes st)
|
|
||||||
st' <- get -- note that the notes may contain refs
|
|
||||||
refs' <- refsToMarkdown opts (reverse $ stRefs st')
|
|
||||||
let render' :: Doc -> String
|
let render' :: Doc -> String
|
||||||
render' = render colwidth
|
render' = render colwidth
|
||||||
let main = render' $ body <>
|
let main = render' $ body <> notesAndRefs'
|
||||||
(if isEmpty notes' then empty else blankline <> notes') <>
|
|
||||||
(if isEmpty refs' then empty else blankline <> refs')
|
|
||||||
let context = defField "toc" (render' toc)
|
let context = defField "toc" (render' toc)
|
||||||
$ defField "body" main
|
$ defField "body" main
|
||||||
$ (if isNullMeta meta
|
$ (if isNullMeta meta
|
||||||
|
@ -337,6 +332,23 @@ beginsWithOrderedListMarker str =
|
||||||
Left _ -> False
|
Left _ -> False
|
||||||
Right _ -> True
|
Right _ -> True
|
||||||
|
|
||||||
|
notesAndRefs :: WriterOptions -> MD Doc
|
||||||
|
notesAndRefs opts = do
|
||||||
|
notes' <- reverse <$> gets stNotes >>= notesToMarkdown opts
|
||||||
|
modify $ \s -> s { stNotes = [] }
|
||||||
|
refs' <- reverse <$> gets stRefs >>= refsToMarkdown opts
|
||||||
|
modify $ \s -> s { stRefs = [] }
|
||||||
|
|
||||||
|
let endSpacing =
|
||||||
|
if | writerReferenceLocation opts == EndOfDocument -> empty
|
||||||
|
| isEmpty notes' && isEmpty refs' -> empty
|
||||||
|
| otherwise -> blankline
|
||||||
|
|
||||||
|
return $
|
||||||
|
(if isEmpty notes' then empty else blankline <> notes') <>
|
||||||
|
(if isEmpty refs' then empty else blankline <> refs') <>
|
||||||
|
endSpacing
|
||||||
|
|
||||||
-- | Convert Pandoc block element to markdown.
|
-- | Convert Pandoc block element to markdown.
|
||||||
blockToMarkdown :: WriterOptions -- ^ Options
|
blockToMarkdown :: WriterOptions -- ^ Options
|
||||||
-> Block -- ^ Block element
|
-> Block -- ^ Block element
|
||||||
|
@ -346,16 +358,7 @@ blockToMarkdown opts blk =
|
||||||
do doc <- blockToMarkdown' opts blk
|
do doc <- blockToMarkdown' opts blk
|
||||||
blkLevel <- asks envBlockLevel
|
blkLevel <- asks envBlockLevel
|
||||||
if writerReferenceLocation opts == EndOfBlock && blkLevel == 1
|
if writerReferenceLocation opts == EndOfBlock && blkLevel == 1
|
||||||
then do st <- get
|
then notesAndRefs opts >>= (\d -> return $ doc <> d)
|
||||||
notes' <- notesToMarkdown opts (reverse $ stNotes st)
|
|
||||||
modify $ \s -> s { stNotes = [] }
|
|
||||||
st' <- get -- note that the notes may contain refs
|
|
||||||
refs' <- refsToMarkdown opts (reverse $ stRefs st')
|
|
||||||
modify $ \s -> s { stRefs = [] }
|
|
||||||
return $ doc <>
|
|
||||||
(if isEmpty notes' then empty else blankline <> notes') <>
|
|
||||||
(if isEmpty refs' then empty else blankline <> refs') <>
|
|
||||||
(if (isEmpty notes' && isEmpty refs') then empty else blankline)
|
|
||||||
else return doc
|
else return doc
|
||||||
|
|
||||||
blockToMarkdown' :: WriterOptions -- ^ Options
|
blockToMarkdown' :: WriterOptions -- ^ Options
|
||||||
|
@ -418,16 +421,7 @@ blockToMarkdown' opts (Header level attr inlines) = do
|
||||||
-- put them here.
|
-- put them here.
|
||||||
blkLevel <- asks envBlockLevel
|
blkLevel <- asks envBlockLevel
|
||||||
refs <- if writerReferenceLocation opts == EndOfSection && blkLevel == 1
|
refs <- if writerReferenceLocation opts == EndOfSection && blkLevel == 1
|
||||||
then do st <- get
|
then notesAndRefs opts
|
||||||
notes' <- notesToMarkdown opts (reverse $ stNotes st)
|
|
||||||
modify $ \s -> s { stNotes = [] }
|
|
||||||
st' <- get -- note that the notes may contain refs
|
|
||||||
refs' <- refsToMarkdown opts (reverse $ stRefs st')
|
|
||||||
modify $ \s -> s { stRefs = [] }
|
|
||||||
return $
|
|
||||||
(if isEmpty notes' then empty else blankline <> notes') <>
|
|
||||||
(if isEmpty refs' then empty else blankline <> refs') <>
|
|
||||||
(if (isEmpty notes' && isEmpty refs') then empty else blankline)
|
|
||||||
else return empty
|
else return empty
|
||||||
|
|
||||||
plain <- asks envPlain
|
plain <- asks envPlain
|
||||||
|
|
Loading…
Reference in a new issue