Markdown reader: warn for notes defined but not used.

Closes #1718.

Parsing.ParserState: Make stateNotes' a Map, add stateNoteRefs.
This commit is contained in:
John MacFarlane 2017-05-25 11:15:52 +02:00
parent 41db9e826e
commit 8f2c803f97
3 changed files with 29 additions and 8 deletions

View file

@ -72,6 +72,7 @@ data LogMessage =
| CouldNotParseYamlMetadata String SourcePos
| DuplicateLinkReference String SourcePos
| DuplicateNoteReference String SourcePos
| NoteDefinedButNotUsed String SourcePos
| DuplicateIdentifier String SourcePos
| ReferenceNotFound String SourcePos
| CircularReference String SourcePos
@ -113,6 +114,11 @@ instance ToJSON LogMessage where
"source" .= Text.pack (sourceName pos),
"line" .= toJSON (sourceLine pos),
"column" .= toJSON (sourceColumn pos)]
NoteDefinedButNotUsed s pos ->
["key" .= Text.pack s,
"source" .= Text.pack (sourceName pos),
"line" .= toJSON (sourceLine pos),
"column" .= toJSON (sourceColumn pos)]
DuplicateNoteReference s pos ->
["contents" .= Text.pack s,
"source" .= Text.pack (sourceName pos),
@ -203,6 +209,9 @@ showLogMessage msg =
"Duplicate link reference '" ++ s ++ "' at " ++ showPos pos
DuplicateNoteReference s pos ->
"Duplicate note reference '" ++ s ++ "' at " ++ showPos pos
NoteDefinedButNotUsed s pos ->
"Note with key '" ++ s ++ "' defined at " ++ showPos pos ++
" but not used."
DuplicateIdentifier s pos ->
"Duplicate identifier '" ++ s ++ "' at " ++ showPos pos
ReferenceNotFound s pos ->
@ -256,6 +265,7 @@ messageVerbosity msg =
CouldNotParseYamlMetadata{} -> WARNING
DuplicateLinkReference{} -> WARNING
DuplicateNoteReference{} -> WARNING
NoteDefinedButNotUsed{} -> WARNING
DuplicateIdentifier{} -> WARNING
ReferenceNotFound{} -> WARNING
CircularReference{} -> WARNING

View file

@ -983,6 +983,7 @@ data ParserState = ParserState
stateSubstitutions :: SubstTable, -- ^ List of substitution references
stateNotes :: NoteTable, -- ^ List of notes (raw bodies)
stateNotes' :: NoteTable', -- ^ List of notes (parsed bodies)
stateNoteRefs :: Set.Set String, -- ^ List of note references used
stateMeta :: Meta, -- ^ Document metadata
stateMeta' :: F Meta, -- ^ Document metadata
stateCitations :: M.Map String String, -- ^ RST-style citations
@ -1099,7 +1100,8 @@ defaultParserState =
stateHeaderKeys = M.empty,
stateSubstitutions = M.empty,
stateNotes = [],
stateNotes' = [],
stateNotes' = M.empty,
stateNoteRefs = Set.empty,
stateMeta = nullMeta,
stateMeta' = return nullMeta,
stateCitations = M.empty,
@ -1166,7 +1168,8 @@ data QuoteContext
type NoteTable = [(String, String)]
type NoteTable' = [(String, F Blocks)] -- used in markdown reader
type NoteTable' = M.Map String (SourcePos, F Blocks)
-- used in markdown reader
newtype Key = Key String deriving (Show, Read, Eq, Ord)

View file

@ -362,6 +362,14 @@ parseMarkdown = do
optional titleBlock
blocks <- parseBlocks
st <- getState
-- check for notes with no corresponding note references
let notesUsed = stateNoteRefs st
let notesDefined = M.keys (stateNotes' st)
mapM_ (\n -> unless (n `Set.member` notesUsed) $ do
-- lookup to get sourcepos
case M.lookup n (stateNotes' st) of
Just (pos, _) -> report (NoteDefinedButNotUsed n pos)
Nothing -> error "The impossible happened.") notesDefined
let doc = runF (do Pandoc _ bs <- B.doc <$> blocks
meta <- stateMeta' st
return $ Pandoc meta bs) st
@ -469,12 +477,11 @@ noteBlock = try $ do
let raw = unlines (first:rest) ++ "\n"
optional blanklines
parsed <- parseFromString' parseBlocks raw
let newnote = (ref, parsed)
oldnotes <- stateNotes' <$> getState
case lookup ref oldnotes of
case M.lookup ref oldnotes of
Just _ -> logMessage $ DuplicateNoteReference ref pos
Nothing -> return ()
updateState $ \s -> s { stateNotes' = newnote : oldnotes }
updateState $ \s -> s { stateNotes' = M.insert ref (pos, parsed) oldnotes }
return mempty
--
@ -1816,16 +1823,17 @@ note :: PandocMonad m => MarkdownParser m (F Inlines)
note = try $ do
guardEnabled Ext_footnotes
ref <- noteMarker
updateState $ \st -> st{ stateNoteRefs = Set.insert ref (stateNoteRefs st) }
return $ do
notes <- asksF stateNotes'
case lookup ref notes of
case M.lookup ref notes of
Nothing -> return $ B.str $ "[^" ++ ref ++ "]"
Just contents -> do
Just (_pos, contents) -> do
st <- askF
-- process the note in a context that doesn't resolve
-- notes, to avoid infinite looping with notes inside
-- notes:
let contents' = runF contents st{ stateNotes' = [] }
let contents' = runF contents st{ stateNotes' = M.empty }
return $ B.note contents'
inlineNote :: PandocMonad m => MarkdownParser m (F Inlines)