-
Notifications
You must be signed in to change notification settings - Fork 5
Commit
This commit does not belong to any branch on this repository, and may belong to a fork outside of the repository.
feat: Add linter to detect sequences of
#defines
that should be enums.
- Loading branch information
Showing
5 changed files
with
166 additions
and
0 deletions.
There are no files selected for viewing
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,99 @@ | ||
{-# LANGUAGE NamedFieldPuns #-} | ||
{-# LANGUAGE OverloadedStrings #-} | ||
{-# LANGUAGE Strict #-} | ||
module Tokstyle.Linter.EnumDefines (analyse) where | ||
|
||
import Control.Monad (when) | ||
import Control.Monad.State.Strict (State) | ||
import qualified Control.Monad.State.Strict as State | ||
import Data.Fix (Fix (..)) | ||
import qualified Data.List as List | ||
import Data.Text (Text) | ||
import qualified Data.Text as Text | ||
import Language.Cimple (Lexeme (..), LiteralType (..), | ||
Node, NodeF (..)) | ||
import Language.Cimple.Diagnostics (HasDiagnostics (..), warn) | ||
import Language.Cimple.TraverseAst (AstActions, astActions, doNode, | ||
traverseAst) | ||
import Text.Casing (fromHumps, fromSnake, toPascal, | ||
toSnake, unIdentifier) | ||
import Text.Read (readMaybe) | ||
|
||
|
||
minSequence :: Int | ||
minSequence = 5 | ||
|
||
minComponents :: Int | ||
minComponents = 2 | ||
|
||
maxSmallInt :: Int | ||
maxSmallInt = 0xff | ||
|
||
data Linter = Linter | ||
{ diags :: [Text] | ||
, defs :: [Text] | ||
} | ||
|
||
instance HasDiagnostics Linter where | ||
addDiagnostic diag l@Linter{diags} = l{diags = addDiagnostic diag diags} | ||
|
||
empty :: Linter | ||
empty = Linter [] [] | ||
|
||
addDef :: Text -> Linter -> Linter | ||
addDef def l@Linter{defs} = l{defs = def:defs} | ||
|
||
clearDefs :: Linter -> Linter | ||
clearDefs l = l{defs = []} | ||
|
||
commonPrefix :: [String] -> String | ||
commonPrefix [] = "" | ||
commonPrefix l = foldl1 go l | ||
where | ||
go _ [] = [] | ||
go [] _ = [] | ||
go (x:xs) (y:ys) | ||
| x == y = x : go xs ys | ||
| otherwise = [] | ||
|
||
|
||
checkEnumDefs :: FilePath -> Node (Lexeme Text) -> State Linter () | ||
checkEnumDefs file node = do | ||
Linter{defs} <- State.get | ||
let cp = commonPrefix $ map Text.unpack defs | ||
when (length defs == minSequence && "_" `List.isSuffixOf` cp && numComponents cp >= minComponents) $ | ||
warn file node $ "sequence of `#define`s longer than " <> Text.pack (show minSequence) | ||
<> " could be written as `enum " <> toEnumName cp <> "`" | ||
|
||
where | ||
numComponents = length . unIdentifier . fromSnake | ||
toEnumName = Text.pack . toSnake . fromHumps . toPascal . fromSnake | ||
|
||
|
||
isSmallInt :: Text -> Bool | ||
isSmallInt txt = | ||
case readMaybe $ Text.unpack txt of | ||
Nothing -> False | ||
Just num -> num <= maxSmallInt | ||
|
||
|
||
linter :: AstActions (State Linter) Text | ||
linter = astActions | ||
{ doNode = \file node act -> | ||
case unFix node of | ||
PreprocDefineConst (L _ _ name) (Fix (LiteralExpr Int (L _ _ num))) | isSmallInt num -> do | ||
State.modify $ addDef name | ||
checkEnumDefs file node | ||
|
||
-- Skip comments, don't clear defs. | ||
Comment{} -> act | ||
|
||
_ -> do | ||
act -- Recurse first, check defs later. | ||
checkEnumDefs file node | ||
-- Clear defs whenever we see a new kind of node (not comment or #define). | ||
State.modify clearDefs | ||
} | ||
|
||
analyse :: (FilePath, [Node (Lexeme Text)]) -> [Text] | ||
analyse = reverse . diags . flip State.execState empty . traverseAst linter |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,61 @@ | ||
{-# LANGUAGE OverloadedStrings #-} | ||
module Tokstyle.Linter.EnumDefinesSpec where | ||
|
||
import Test.Hspec (Spec, it, shouldBe) | ||
|
||
import Tokstyle.Linter (allWarnings, analyseLocal) | ||
import Tokstyle.LinterSpec (mustParse) | ||
|
||
|
||
spec :: Spec | ||
spec = do | ||
it "suggests using enums for long sequences of #defines" $ do | ||
ast <- mustParse | ||
[ "#define FOO_BAR_ONE 1" | ||
, "#define FOO_BAR_TWO 2" | ||
, "#define FOO_BAR_THREE 3" | ||
, "#define FOO_BAR_FOUR 4" | ||
, "#define FOO_BAR_FIVE 5" | ||
] | ||
analyseLocal allWarnings ("test.c", ast) | ||
`shouldBe` | ||
[ "test.c:5: sequence of `#define`s longer than 5 could be written as `enum Foo_Bar` [-Wenum-defines]" | ||
] | ||
|
||
it "allows comments to be interspersed in the enum" $ do | ||
ast <- mustParse | ||
[ "#define FOO_BAR_ONE 1" | ||
, "#define FOO_BAR_TWO 2" | ||
, "// some comment here" | ||
, "#define FOO_BAR_THREE 3" | ||
, "/* another comment here */" | ||
, "#define FOO_BAR_FOUR 4" | ||
, "#define FOO_BAR_FIVE 5" | ||
] | ||
analyseLocal allWarnings ("test.c", ast) | ||
`shouldBe` | ||
[ "test.c:7: sequence of `#define`s longer than 5 could be written as `enum Foo_Bar` [-Wenum-defines]" | ||
] | ||
|
||
it "ignores broken sequences" $ do | ||
ast <- mustParse | ||
[ "#define FOO_BAR_ONE 1" | ||
, "#define FOO_BAR_TWO 2" | ||
, "static const uint32_t xxx = 10;" -- breaks the sequence, we ignore this because it doesn't look like an enum | ||
, "#define FOO_BAR_THREE 3" | ||
, "#define FOO_BAR_FOUR 4" | ||
, "#define FOO_BAR_FIVE 5" | ||
] | ||
analyseLocal allWarnings ("test.c", ast) | ||
`shouldBe` [] | ||
|
||
it "ignores defines with large values" $ do | ||
ast <- mustParse | ||
[ "#define FOO_BAR_ONE 1" | ||
, "#define FOO_BAR_TWO 0x20" | ||
, "#define FOO_BAR_THREE 300" | ||
, "#define FOO_BAR_FOUR 4" | ||
, "#define FOO_BAR_FIVE 5" | ||
] | ||
analyseLocal allWarnings ("test.c", ast) | ||
`shouldBe` [] |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters