@@ -512,10 +512,21 @@ paraUntil end = do
512512 guard $ not $ museInPara state
513513 first (fmap B. para) <$> paraContentsUntil end
514514
515- noteMarker :: PandocMonad m => MuseParser m String
516- noteMarker = try $ do
517- char ' ['
518- (:) <$> oneOf " 123456789" <*> manyTill digit (char ' ]' )
515+ noteBrackets :: NoteType -> (Char , Char )
516+ noteBrackets nt =
517+ case nt of
518+ Endnote -> (' {' , ' }' )
519+ _ -> (' [' , ' ]' )
520+
521+ noteMarker :: PandocMonad m => NoteType -> MuseParser m (NoteType , String )
522+ noteMarker nt = try $ do
523+ char l
524+ m <- (:) <$> oneOf " 123456789" <*> manyTill digit (char r)
525+ return (nt, [l] ++ m ++ [r])
526+ where (l, r) = noteBrackets nt
527+
528+ anyNoteMarker :: PandocMonad m => MuseParser m (NoteType , String )
529+ anyNoteMarker = noteMarker Footnote <|> noteMarker Endnote
519530
520531-- Amusewiki version of note
521532-- Parsing is similar to list item, except that note marker is used instead of list marker
@@ -524,7 +535,7 @@ amuseNoteBlockUntil :: PandocMonad m
524535 -> MuseParser m (F Blocks , a )
525536amuseNoteBlockUntil end = try $ do
526537 guardEnabled Ext_amuse
527- ref <- noteMarker <* spaceChar
538+ (_, ref) <- anyNoteMarker <* spaceChar
528539 pos <- getPosition
529540 updateState (\ st -> st { museInPara = False })
530541 (content, e) <- listItemContentsUntil (sourceColumn pos - 1 ) (fail " x" ) end
@@ -540,7 +551,7 @@ emacsNoteBlock :: PandocMonad m => MuseParser m (F Blocks)
540551emacsNoteBlock = try $ do
541552 guardDisabled Ext_amuse
542553 pos <- getPosition
543- ref <- noteMarker <* skipSpaces
554+ (_, ref) <- anyNoteMarker <* skipSpaces
544555 content <- mconcat <$> blocksTillNote
545556 oldnotes <- museNotes <$> getState
546557 when (M. member ref oldnotes)
@@ -549,7 +560,7 @@ emacsNoteBlock = try $ do
549560 return mempty
550561 where
551562 blocksTillNote =
552- many1Till parseBlock (eof <|> () <$ lookAhead noteMarker )
563+ many1Till parseBlock (eof <|> () <$ lookAhead anyNoteMarker )
553564
554565--
555566-- Verse markup
@@ -828,15 +839,15 @@ footnote :: PandocMonad m => MuseParser m (F Inlines)
828839footnote = try $ do
829840 inLink <- museInLink <$> getState
830841 guard $ not inLink
831- ref <- noteMarker
842+ (notetype, ref) <- anyNoteMarker
832843 return $ do
833844 notes <- asksF museNotes
834845 case M. lookup ref notes of
835- Nothing -> return $ B. str $ " [ " ++ ref ++ " ] "
846+ Nothing -> return $ B. str ref
836847 Just (_pos, contents) -> do
837848 st <- askF
838849 let contents' = runF contents st { museNotes = M. delete ref (museNotes st) }
839- return $ B. note contents'
850+ return $ B. singleton $ Note notetype $ B. toList contents'
840851
841852whitespace :: PandocMonad m => MuseParser m (F Inlines )
842853whitespace = try $ do
0 commit comments