Skip to content

Commit 4335bf2

Browse files
author
Alexander Krotov
committed
Muse writer: add endnote support
1 parent 30a2583 commit 4335bf2

File tree

2 files changed

+28
-11
lines changed

2 files changed

+28
-11
lines changed

src/Text/Pandoc/Writers/Muse.hs

Lines changed: 23 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -59,6 +59,7 @@ import qualified Data.Set as Set
5959
type Notes = [[Block]]
6060
data WriterState =
6161
WriterState { stNotes :: Notes
62+
, stEndNotes :: Notes
6263
, stOptions :: WriterOptions
6364
, stTopLevel :: Bool
6465
, stInsideBlock :: Bool
@@ -72,6 +73,7 @@ writeMuse :: PandocMonad m
7273
-> m Text
7374
writeMuse opts document =
7475
let st = WriterState { stNotes = []
76+
, stEndNotes = []
7577
, stOptions = opts
7678
, stTopLevel = True
7779
, stInsideBlock = False
@@ -95,8 +97,9 @@ pandocToMuse (Pandoc meta blocks) = do
9597
(fmap render' . inlineListToMuse)
9698
meta
9799
body <- blockListToMuse blocks
98-
notes <- liftM (reverse . stNotes) get >>= notesToMuse
99-
let main = render colwidth $ body $+$ notes
100+
notes <- liftM (reverse . stNotes) get >>= notesToMuse ('[', ']')
101+
endNotes <- liftM (reverse . stEndNotes) get >>= notesToMuse ('{', '}')
102+
let main = render colwidth $ body $+$ notes $+$ endNotes
100103
let context = defField "body" main metadata
101104
case writerTemplate opts of
102105
Nothing -> return main
@@ -261,18 +264,20 @@ blockToMuse Null = return empty
261264

262265
-- | Return Muse representation of notes.
263266
notesToMuse :: PandocMonad m
264-
=> Notes
267+
=> (Char, Char)
268+
-> Notes
265269
-> StateT WriterState m Doc
266-
notesToMuse notes = liftM vsep (zipWithM noteToMuse [1 ..] notes)
270+
notesToMuse lr notes = liftM vsep (zipWithM (noteToMuse lr) [1 ..] notes)
267271

268272
-- | Return Muse representation of a note.
269273
noteToMuse :: PandocMonad m
270-
=> Int
274+
=> (Char, Char)
275+
-> Int
271276
-> [Block]
272277
-> StateT WriterState m Doc
273-
noteToMuse num note = do
278+
noteToMuse (l, r) num note = do
274279
contents <- blockListToMuse note
275-
let marker = "[" ++ show num ++ "] "
280+
let marker = l : (show num ++ (r : " "))
276281
return $ hang (length marker) (text marker) contents
277282

278283
-- | Escape special characters for Muse.
@@ -391,12 +396,19 @@ inlineToMuse (Image _ inlines (source, title)) = do
391396
else "[" <> alt <> "]"
392397
else "[" <> text title <> "]"
393398
return $ "[[" <> text source <> "]" <> title' <> "]"
394-
inlineToMuse (Note _ contents) = do
399+
inlineToMuse (Note notetype contents) = do
395400
-- add to notes in state
396401
notes <- gets stNotes
397-
modify $ \st -> st { stNotes = contents:notes }
398-
let ref = show $ length notes + 1
399-
return $ "[" <> text ref <> "]"
402+
endNotes <- gets stEndNotes
403+
modify $ case notetype of
404+
EndNote -> \st -> st { stEndNotes = contents:endNotes }
405+
_ -> \st -> st { stNotes = contents:notes }
406+
let ref = show $ 1 + length (case notetype of
407+
EndNote -> endNotes
408+
_ -> notes)
409+
case notetype of
410+
EndNote -> return $ "{" <> text ref <> "}"
411+
_ -> return $ "[" <> text ref <> "]"
400412
inlineToMuse (Span (_,name:_,_) inlines) = do
401413
contents <- inlineListToMuse inlines
402414
return $ "<class name=\"" <> text name <> "\">" <> contents <> "</class>"

test/Tests/Writers/Muse.hs

Lines changed: 5 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -343,6 +343,11 @@ tests = [ testGroup "block elements"
343343
, ""
344344
, "[1] Foo"
345345
]
346+
, "endnote" =: endNote (plain (text "Foo"))
347+
=?> unlines [ "{1}"
348+
, ""
349+
, "{1} Foo"
350+
]
346351
, "span" =: spanWith ("",["foobar"],[]) (str "Some text")
347352
=?> "<class name=\"foobar\">Some text</class>"
348353
, testGroup "combined"

0 commit comments

Comments
 (0)