Skip to content

Commit

Permalink
fix: Add exemption for in -Wparens for if ((x)).
Browse files Browse the repository at this point in the history
This is used to silence warnings about constant if statements like:
```
if ((true)) {
    return 2;
}

return 3;
```
  • Loading branch information
iphydf committed Apr 6, 2022
1 parent 885128e commit 8b75201
Show file tree
Hide file tree
Showing 3 changed files with 34 additions and 0 deletions.
4 changes: 4 additions & 0 deletions src/Tokstyle/Linter/Parens.hs
Original file line number Diff line number Diff line change
Expand Up @@ -6,6 +6,7 @@ module Tokstyle.Linter.Parens (analyse) where
import Control.Monad.State.Strict (State)
import qualified Control.Monad.State.Strict as State
import Data.Fix (Fix (..))
import Data.Maybe (maybeToList)
import Data.Text (Text)
import Language.Cimple (Lexeme (..), Node, NodeF (..))
import Language.Cimple.Diagnostics (warn)
Expand Down Expand Up @@ -39,6 +40,9 @@ linter = astActions
mapM_ (checkArg file) args
act

IfStmt (Fix (ParenExpr c)) t e ->
traverseAst linter (file, [c, t] ++ maybeToList e)

Return (Just (Fix ParenExpr{})) -> do
warn file node "return expression does not need parentheses"
act
Expand Down
29 changes: 29 additions & 0 deletions test/Tokstyle/Linter/ParensSpec.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,29 @@
{-# LANGUAGE OverloadedStrings #-}
module Tokstyle.Linter.ParensSpec where

import Test.Hspec (Spec, it, shouldBe)

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


spec :: Spec
spec = do
it "warns about parentheses around return expressions" $ do
ast <- mustParse
[ "int a(int b) {"
, " return (1 + 2);"
, "}"
]
analyse allWarnings ("test.c", ast)
`shouldBe`
[ "test.c:2: return expression does not need parentheses [-Wparens]"
]

it "does not warn about parens in if conditions" $ do
ast <- mustParse
[ "int a(int b) {"
, " if ((true)) { return 3; }"
, "}"
]
analyse allWarnings ("test.c", ast) `shouldBe` []
1 change: 1 addition & 0 deletions tokstyle.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -135,6 +135,7 @@ test-suite testsuite
, Tokstyle.Linter.CallocTypeSpec
, Tokstyle.Linter.CompoundInitSpec
, Tokstyle.Linter.ConstnessSpec
, Tokstyle.Linter.ParensSpec
, Tokstyle.Linter.SwitchIfSpec
, Tokstyle.Linter.TypeCheckSpec
, Tokstyle.Linter.VarUnusedInScopeSpec
Expand Down

0 comments on commit 8b75201

Please sign in to comment.