diff --git a/src/Tokstyle/Cimple/Analysis.hs b/src/Tokstyle/Cimple/Analysis.hs index 018ff6e..dd03c9d 100644 --- a/src/Tokstyle/Cimple/Analysis.hs +++ b/src/Tokstyle/Cimple/Analysis.hs @@ -13,6 +13,7 @@ import qualified Tokstyle.Cimple.Analysis.GlobalFuncs as GlobalFuncs import qualified Tokstyle.Cimple.Analysis.LoggerCalls as LoggerCalls import qualified Tokstyle.Cimple.Analysis.LoggerNoEscapes as LoggerNoEscapes +import qualified Tokstyle.Cimple.Analysis.DeclsHaveDefns as DeclsHaveDefns import qualified Tokstyle.Cimple.Analysis.DocComments as DocComments type TranslationUnit = (FilePath, [Node (Lexeme Text)]) @@ -29,5 +30,6 @@ analyse (file, ast) = concatMap (\f -> f file ast) analyseGlobal :: [TranslationUnit] -> [Text] analyseGlobal tus = concatMap ($ tus) - [ DocComments.analyse + [ DeclsHaveDefns.analyse + , DocComments.analyse ] diff --git a/src/Tokstyle/Cimple/Analysis/DeclsHaveDefns.hs b/src/Tokstyle/Cimple/Analysis/DeclsHaveDefns.hs new file mode 100644 index 0000000..ce6fec8 --- /dev/null +++ b/src/Tokstyle/Cimple/Analysis/DeclsHaveDefns.hs @@ -0,0 +1,62 @@ +{-# LANGUAGE NamedFieldPuns #-} +{-# LANGUAGE OverloadedStrings #-} +{-# LANGUAGE StrictData #-} +module Tokstyle.Cimple.Analysis.DeclsHaveDefns (analyse) where + +import Control.Monad.State.Lazy (State) +import qualified Control.Monad.State.Lazy as State +import Data.Map (Map) +import qualified Data.Map as Map +import Data.Maybe (mapMaybe) +import Data.Text (Text) +import Language.Cimple (Lexeme (..), LexemeClass (..), + Node (..)) +import qualified Language.Cimple.Diagnostics as Diagnostics +import Language.Cimple.TraverseAst (AstActions (..), defaultActions, + traverseAst) +import System.FilePath (takeFileName) + + +data DeclDefn = DeclDefn + { decl :: Maybe (FilePath, Lexeme Text) + , defn :: Maybe (FilePath, Lexeme Text) + } + + +collectPairs :: AstActions (State (Map Text DeclDefn)) Text +collectPairs = defaultActions + { doNode = \file node act -> + case node of + FunctionDecl _ (FunctionPrototype _ fn@(L _ IdVar fname) _) _ -> do + State.modify $ \pairs -> + case Map.lookup fname pairs of + Nothing -> Map.insert fname (DeclDefn{ decl = Just (file, fn), defn = Nothing }) pairs + Just dd -> Map.insert fname (dd { decl = Just (file, fn) }) pairs + act + + FunctionDefn _ (FunctionPrototype _ fn@(L _ IdVar fname) _) _ -> do + State.modify $ \pairs -> + case Map.lookup fname pairs of + Nothing -> Map.insert fname (DeclDefn{ decl = Nothing, defn = Just (file, fn) }) pairs + Just dd -> Map.insert fname (dd { defn = Just (file, fn) }) pairs + act + + _ -> act + } + where + +analyse :: [(FilePath, [Node (Lexeme Text)])] -> [Text] +analyse tus = + map makeDiagnostic + . mapMaybe lacksDefn + . Map.elems + . flip State.execState Map.empty + . traverseAst collectPairs + . filter (not . (`elem` ["ccompat.h", "tox.h"]) . takeFileName . fst) + $ tus + where + lacksDefn DeclDefn{decl, defn = Nothing} = decl + lacksDefn _ = Nothing + + makeDiagnostic (file, fn@(L _ _ fname)) = + Diagnostics.sloc file fn <> ": missing definition for `" <> fname <> "'" diff --git a/src/Tokstyle/Cimple/Analysis/DocComments.hs b/src/Tokstyle/Cimple/Analysis/DocComments.hs index 75231e0..1452226 100644 --- a/src/Tokstyle/Cimple/Analysis/DocComments.hs +++ b/src/Tokstyle/Cimple/Analysis/DocComments.hs @@ -32,12 +32,12 @@ linter :: AstActions (State Linter) Text linter = defaultActions { doNode = \file node act -> case node of - Commented doc (FunctionDecl _ (FunctionPrototype _ fn@(L _ IdVar _) _) _) -> do - checkCommentEquals file doc fn + Commented doc (FunctionDecl _ (FunctionPrototype _ (L _ IdVar fname) _) _) -> do + checkCommentEquals file doc fname act - Commented doc (FunctionDefn _ (FunctionPrototype _ fn@(L _ IdVar _) _) _) -> do - checkCommentEquals file doc fn + Commented doc (FunctionDefn _ (FunctionPrototype _ (L _ IdVar fname) _) _) -> do + checkCommentEquals file doc fname act {- @@ -55,16 +55,17 @@ linter = defaultActions removeSloc :: Node (Lexeme a) -> Node (Lexeme a) removeSloc = fmap $ \(L _ c t) -> L (AlexPn 0 0 0) c t - checkCommentEquals file doc fn@(L _ _ fname) = do + checkCommentEquals file doc fname = do l@Linter{docs} <- State.get case lookup fname docs of Nothing -> State.put l{docs = (fname, (file, doc)):docs} Just (_, doc') | removeSloc doc == removeSloc doc' -> return () - Just (file', doc') -> - warn file fn $ "comment on declaration does not match definition:\n" - <> tshow (ppTranslationUnit [doc]) <> "\nalso defined at " - <> Diagnostics.sloc file' (Diagnostics.at doc') <> ":\n" + Just (file', doc') -> do + warn file (Diagnostics.at doc) $ "comment on definition of `" <> fname + <> "' does not match declaration:\n" + <> tshow (ppTranslationUnit [doc]) + warn file' (Diagnostics.at doc') $ "mismatching comment found here:\n" <> tshow (ppTranslationUnit [doc']) analyse :: [(FilePath, [Node (Lexeme Text)])] -> [Text] -analyse tus = reverse . diags $ State.execState (traverseAst linter tus) empty +analyse tus = reverse . diags $ State.execState (traverseAst linter $ reverse tus) empty diff --git a/tokstyle.cabal b/tokstyle.cabal index 25f0f1d..9602850 100644 --- a/tokstyle.cabal +++ b/tokstyle.cabal @@ -20,7 +20,8 @@ library exposed-modules: Tokstyle.Cimple.Analysis other-modules: - Tokstyle.Cimple.Analysis.DocComments + Tokstyle.Cimple.Analysis.DeclsHaveDefns + , Tokstyle.Cimple.Analysis.DocComments , Tokstyle.Cimple.Analysis.ForLoops , Tokstyle.Cimple.Analysis.FuncPrototypes , Tokstyle.Cimple.Analysis.FuncScopes