@@ -335,21 +335,31 @@ para = do
335335 endOfPara = try $ blankline >> skipMany1 blankline
336336 newBlockElement = try $ blankline >> void blockElements
337337
338- noteMarker :: PandocMonad m => MuseParser m String
339- noteMarker = try $ do
340- char ' ['
338+ noteBrackets :: NoteType -> (Char , Char )
339+ noteBrackets nt =
340+ case nt of
341+ EndNote -> (' {' , ' }' )
342+ _ -> (' [' , ' ]' )
343+
344+ noteMarker :: PandocMonad m => NoteType -> MuseParser m (NoteType , String )
345+ noteMarker nt = try $ do
346+ char l
341347 first <- oneOf " 123456789"
342- rest <- manyTill digit (char ' ]' )
343- return $ first: rest
348+ rest <- manyTill digit (char r)
349+ return (nt, [l] ++ (first: rest) ++ [r])
350+ where (l, r) = noteBrackets nt
351+
352+ anyNoteMarker :: PandocMonad m => MuseParser m (NoteType , String )
353+ anyNoteMarker = noteMarker FootNote <|> noteMarker EndNote
344354
345355-- Amusewiki version of note
346356-- Parsing is similar to list item, except that note marker is used instead of list marker
347357amuseNoteBlock :: PandocMonad m => MuseParser m (F Blocks )
348358amuseNoteBlock = try $ do
349359 guardEnabled Ext_amuse
350360 pos <- getPosition
351- ref <- noteMarker <* spaceChar
352- content <- listItemContents $ 3 + length ref
361+ (_, ref) <- anyNoteMarker <* spaceChar
362+ content <- listItemContents $ 1 + length ref
353363 oldnotes <- stateNotes' <$> getState
354364 case M. lookup ref oldnotes of
355365 Just _ -> logMessage $ DuplicateNoteReference ref pos
@@ -363,7 +373,7 @@ emacsNoteBlock :: PandocMonad m => MuseParser m (F Blocks)
363373emacsNoteBlock = try $ do
364374 guardDisabled Ext_amuse
365375 pos <- getPosition
366- ref <- noteMarker <* skipSpaces
376+ (_, ref) <- anyNoteMarker <* skipSpaces
367377 content <- mconcat <$> blocksTillNote
368378 oldnotes <- stateNotes' <$> getState
369379 case M. lookup ref oldnotes of
@@ -373,7 +383,7 @@ emacsNoteBlock = try $ do
373383 return mempty
374384 where
375385 blocksTillNote =
376- many1Till block (eof <|> () <$ lookAhead noteMarker )
386+ many1Till block (eof <|> () <$ lookAhead anyNoteMarker )
377387
378388--
379389-- Verse markup
@@ -647,15 +657,15 @@ anchor = try $ do
647657
648658footnote :: PandocMonad m => MuseParser m (F Inlines )
649659footnote = try $ do
650- ref <- noteMarker
660+ (notetype, ref) <- anyNoteMarker
651661 return $ do
652662 notes <- asksF stateNotes'
653663 case M. lookup ref notes of
654- Nothing -> return $ B. str $ " [ " ++ ref ++ " ] "
664+ Nothing -> return $ B. str ref
655665 Just (_pos, contents) -> do
656666 st <- askF
657667 let contents' = runF contents st { stateNotes' = M. empty }
658- return $ B. note contents'
668+ return $ B. singleton $ Note notetype $ B. toList contents'
659669
660670whitespace :: PandocMonad m => MuseParser m (F Inlines )
661671whitespace = fmap return (lb <|> regsp)
0 commit comments