Skip to content

Commit

Permalink
feat: Add linter to detect ifs that should be switches.
Browse files Browse the repository at this point in the history
  • Loading branch information
iphydf committed Apr 2, 2022
1 parent d0ce039 commit aa2c0f8
Show file tree
Hide file tree
Showing 4 changed files with 202 additions and 0 deletions.
2 changes: 2 additions & 0 deletions src/Tokstyle/Linter.hs
Original file line number Diff line number Diff line change
Expand Up @@ -31,6 +31,7 @@ import qualified Tokstyle.Linter.MemcpyStructs as MemcpyStructs
import qualified Tokstyle.Linter.MissingNonNull as MissingNonNull
import qualified Tokstyle.Linter.NonNull as NonNull
import qualified Tokstyle.Linter.Parens as Parens
import qualified Tokstyle.Linter.SwitchIf as SwitchIf
import qualified Tokstyle.Linter.TypedefName as TypedefName
import qualified Tokstyle.Linter.UnsafeFunc as UnsafeFunc
import qualified Tokstyle.Linter.VarUnusedInScope as VarUnusedInScope
Expand Down Expand Up @@ -72,6 +73,7 @@ localLinters =
, ("missing-non-null" , MissingNonNull.analyse )
, ("non-null" , NonNull.analyse )
, ("parens" , Parens.analyse )
, ("switch-if" , SwitchIf.analyse )
, ("typedef-name" , TypedefName.analyse )
, ("unsafe-func" , UnsafeFunc.analyse )
, ("var-unused-in-scope", VarUnusedInScope.analyse )
Expand Down
71 changes: 71 additions & 0 deletions src/Tokstyle/Linter/SwitchIf.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,71 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE Strict #-}
{-# LANGUAGE StrictData #-}
module Tokstyle.Linter.SwitchIf (analyse) where

import Control.Monad.State.Strict (State)
import qualified Control.Monad.State.Strict as State
import Data.Fix (Fix (..))
import Data.List (nub)
import Data.Text (Text)
import Language.Cimple (BinaryOp (..), Lexeme (..),
LiteralType (..), Node,
NodeF (..), lexemeText)
import Language.Cimple.Diagnostics (warn)
import Language.Cimple.TraverseAst (AstActions, astActions, doNode,
traverseAst)


pattern EqualsConst :: Lexeme Text -> Node (Lexeme Text)
pattern EqualsConst lhs <- Fix (BinaryExpr (Fix (VarExpr lhs)) BopEq (Fix (LiteralExpr ConstId _)))


data IfInfo = IfInfo
{ ifConds :: Maybe [(Text, Lexeme Text)]
, ifBranches :: [Node (Lexeme Text)]
} deriving (Show)

instance Semigroup IfInfo where
a <> b = IfInfo ((<>) <$> ifConds a <*> ifConds b) (ifBranches a <> ifBranches b)


collectInfo :: Node (Lexeme Text) -> IfInfo
collectInfo (Fix (IfStmt (EqualsConst lhs) t Nothing)) =
IfInfo (Just [(lexemeText lhs, lhs)]) [t]
collectInfo (Fix (IfStmt (EqualsConst lhs) t (Just e))) =
IfInfo (Just [(lexemeText lhs, lhs)]) [t] <> collectInfo e
collectInfo (Fix (IfStmt _ t Nothing)) =
IfInfo Nothing [t]
collectInfo (Fix (IfStmt _ t (Just e))) =
IfInfo Nothing [t] <> collectInfo e
collectInfo e =
IfInfo (Just []) [e]


shouldDiagnose :: [(Text, Lexeme Text)] -> [Node (Lexeme Text)] -> Bool
shouldDiagnose cs branches =
length cs >= 2 && length (nub $ map fst cs) == 1 && not (all singleStatement branches)
where
singleStatement (Fix (CompoundStmt [_])) = True
singleStatement _ = False


linter :: AstActions (State [Text]) Text
linter = astActions
{ doNode = \file node act ->
case unFix node of
IfStmt{} -> do
let info = collectInfo node
case ifConds info of
Just cs@((_, c):_) | shouldDiagnose cs (ifBranches info) ->
warn file c "if-statement could be a switch"
_ -> return ()
traverseAst linter (file, ifBranches info)

_ -> act
}


analyse :: (FilePath, [Node (Lexeme Text)]) -> [Text]
analyse = reverse . flip State.execState [] . traverseAst linter
126 changes: 126 additions & 0 deletions test/Tokstyle/Linter/SwitchIfSpec.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,126 @@
{-# LANGUAGE OverloadedStrings #-}
module Tokstyle.Linter.SwitchIfSpec where

import Test.Hspec (Spec, it, shouldBe)

import Tokstyle.Linter (analyse)
import Tokstyle.LinterSpec (mustParse)


spec :: Spec
spec = do
it "accepts a single if/else" $ do
ast <- mustParse
[ "bool a(int b) {"
, " if (b == THE_FOO) {"
, " print_int(b);"
, " return true;"
, " } else {"
, " return false;"
, " }"
, "}"
]
analyse ["switch-if"] ("test.c", ast) `shouldBe` []

it "ignores candidates where all branches are single statements" $ do
ast <- mustParse
[ "int a(int b) {"
, " if (b == THE_FOO) {"
, " return 0;"
, " } else if (b == THE_BAR) {"
, " return 1;"
, " }"
, "}"
]
analyse ["switch-if"] ("test.c", ast) `shouldBe` []

it "diagnoses a series of if/else-if statements as candidate for switch" $ do
ast <- mustParse
[ "int a(int b) {"
, " if (b == THE_FOO) {"
, " print_int(b);"
, " return 0;"
, " } else if (b == THE_BAR) {"
, " return 1;"
, " }"
, "}"
]
analyse ["switch-if"] ("test.c", ast)
`shouldBe`
[ "test.c:2: if-statement could be a switch [-Wswitch-if]"
]

it "diagnoses a series of if/else-if statements ending in `else` as candidate for switch" $ do
ast <- mustParse
[ "int a(int b) {"
, " if (b == THE_FOO) {"
, " print_int(b);"
, " return 0;"
, " } else if (b == THE_BAR) {"
, " return 1;"
, " } else {"
, " return 2;"
, " }"
, "}"
]
analyse ["switch-if"] ("test.c", ast)
`shouldBe`
[ "test.c:2: if-statement could be a switch [-Wswitch-if]"
]

it "diagnoses a candidates for switch nested inside another `if`" $ do
ast <- mustParse
[ "int a(int b) {"
, " if (b != something) {"
, " if (b == THE_FOO) {"
, " print_int(b);"
, " return 0;"
, " } else if (b == THE_BAR) {"
, " return 1;"
, " } else {"
, " return 2;"
, " }"
, " }"
, "}"
]
analyse ["switch-if"] ("test.c", ast)
`shouldBe`
[ "test.c:3: if-statement could be a switch [-Wswitch-if]"
]

it "diagnoses a candidates for switch nested inside an `else if`" $ do
ast <- mustParse
[ "int a(int b) {"
, " if (b != something) {"
, " /* nop */"
, " } else if (b != another_thing) {"
, " if (b == THE_FOO) {"
, " print_int(b);"
, " return 0;"
, " } else if (b == THE_BAR) {"
, " return 1;"
, " } else {"
, " return 2;"
, " }"
, " }"
, "}"
]
analyse ["switch-if"] ("test.c", ast)
`shouldBe`
[ "test.c:5: if-statement could be a switch [-Wswitch-if]"
]

it "ignores if/else-if statements with different comparison targets" $ do
ast <- mustParse
[ "int a(int b, int c) {"
, " if (b == THE_FOO) {"
, " print_int(b);"
, " return 0;"
, " } else if (c == THE_BAR) {"
, " return 1;"
, " } else {"
, " return 2;"
, " }"
, "}"
]
analyse ["switch-if"] ("test.c", ast) `shouldBe` []
3 changes: 3 additions & 0 deletions tokstyle.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -46,6 +46,7 @@ library
, Tokstyle.Linter.MissingNonNull
, Tokstyle.Linter.NonNull
, Tokstyle.Linter.Parens
, Tokstyle.Linter.SwitchIf
, Tokstyle.Linter.TypeCheck
, Tokstyle.Linter.TypedefName
, Tokstyle.Linter.UnsafeFunc
Expand Down Expand Up @@ -130,9 +131,11 @@ test-suite testsuite
Tokstyle.LinterSpec
, Tokstyle.Linter.BooleansSpec
, Tokstyle.Linter.BooleanReturnSpec
, Tokstyle.Linter.CallgraphSpec
, Tokstyle.Linter.CallocTypeSpec
, Tokstyle.Linter.CompoundInitSpec
, Tokstyle.Linter.ConstnessSpec
, Tokstyle.Linter.SwitchIfSpec
, Tokstyle.Linter.TypeCheckSpec
, Tokstyle.Linter.VarUnusedInScopeSpec
ghc-options:
Expand Down

0 comments on commit aa2c0f8

Please sign in to comment.