@@ -334,19 +334,30 @@ para = do
334334 endOfPara = try $ blankline >> skipMany1 blankline
335335 newBlockElement = try $ blankline >> void blockElements
336336
337- noteMarker :: PandocMonad m => MuseParser m String
338- noteMarker = try $ do
339- char ' ['
340- many1Till digit $ char ' ]'
337+ noteBrackets :: NoteType -> (Char , Char )
338+ noteBrackets nt =
339+ case nt of
340+ EndNote -> (' {' , ' }' )
341+ _ -> (' [' , ' ]' )
342+
343+ noteMarker :: PandocMonad m => NoteType -> MuseParser m (NoteType , String )
344+ noteMarker nt = try $ do
345+ char l
346+ ref <- many1Till digit $ char r
347+ return (nt, [l] ++ ref ++ [r])
348+ where (l, r) = noteBrackets nt
349+
350+ anyNoteMarker :: PandocMonad m => MuseParser m (NoteType , String )
351+ anyNoteMarker = noteMarker FootNote <|> noteMarker EndNote
341352
342353-- Amusewiki version of note
343354-- Parsing is similar to list item, except that note marker is used instead of list marker
344355amuseNoteBlock :: PandocMonad m => MuseParser m (F Blocks )
345356amuseNoteBlock = try $ do
346357 guardEnabled Ext_amuse
347358 pos <- getPosition
348- ref <- noteMarker <* spaceChar
349- content <- listItemContents $ 3 + length ref
359+ (_, ref) <- anyNoteMarker <* spaceChar
360+ content <- listItemContents $ 1 + length ref
350361 oldnotes <- stateNotes' <$> getState
351362 case M. lookup ref oldnotes of
352363 Just _ -> logMessage $ DuplicateNoteReference ref pos
@@ -360,7 +371,7 @@ emacsNoteBlock :: PandocMonad m => MuseParser m (F Blocks)
360371emacsNoteBlock = try $ do
361372 guardDisabled Ext_amuse
362373 pos <- getPosition
363- ref <- noteMarker <* skipSpaces
374+ (_, ref) <- anyNoteMarker <* skipSpaces
364375 content <- mconcat <$> blocksTillNote
365376 oldnotes <- stateNotes' <$> getState
366377 case M. lookup ref oldnotes of
@@ -370,7 +381,7 @@ emacsNoteBlock = try $ do
370381 return mempty
371382 where
372383 blocksTillNote =
373- many1Till block (eof <|> () <$ lookAhead noteMarker )
384+ many1Till block (eof <|> () <$ lookAhead anyNoteMarker )
374385
375386--
376387-- Verse markup
@@ -640,15 +651,15 @@ anchor = try $ do
640651
641652footnote :: PandocMonad m => MuseParser m (F Inlines )
642653footnote = try $ do
643- ref <- noteMarker
654+ (notetype, ref) <- anyNoteMarker
644655 return $ do
645656 notes <- asksF stateNotes'
646657 case M. lookup ref notes of
647- Nothing -> return $ B. str $ " [ " ++ ref ++ " ] "
658+ Nothing -> return $ B. str ref
648659 Just (_pos, contents) -> do
649660 st <- askF
650661 let contents' = runF contents st { stateNotes' = M. empty }
651- return $ B. note contents'
662+ return $ B. singleton $ Note notetype $ B. toList contents'
652663
653664whitespace :: PandocMonad m => MuseParser m (F Inlines )
654665whitespace = fmap return (lb <|> regsp)
0 commit comments