{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE Strict #-}
module Tokstyle.Linter.Booleans (descr) where
import Control.Monad.State.Strict (State)
import qualified Control.Monad.State.Strict as State
import Data.Fix (Fix (..))
import Data.Text (Text)
import qualified Data.Text as Text
import Language.Cimple (Lexeme, LiteralType (..), Node,
NodeF (..))
import Language.Cimple.Diagnostics (warn)
import Language.Cimple.TraverseAst (AstActions, astActions, doNode,
traverseAst)
pattern ReturnBool, OnlyReturnBool :: Node a
pattern $mReturnBool :: forall r a. Node a -> (Void# -> r) -> (Void# -> r) -> r
ReturnBool <- Fix (Return (Just (Fix (LiteralExpr Bool _))))
pattern $mOnlyReturnBool :: forall r a. Node a -> (Void# -> r) -> (Void# -> r) -> r
OnlyReturnBool <- Fix (CompoundStmt [ReturnBool])
checkStmts :: FilePath -> [Node (Lexeme Text)] -> State [Text] ()
checkStmts :: FilePath -> [Node (Lexeme Text)] -> State [Text] ()
checkStmts FilePath
_ [] = () -> State [Text] ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
checkStmts FilePath
file [s :: Node (Lexeme Text)
s@(Fix (IfStmt Node (Lexeme Text)
_ Node (Lexeme Text)
OnlyReturnBool Maybe (Node (Lexeme Text))
Nothing)), Node (Lexeme Text)
ReturnBool] =
FilePath -> Node (Lexeme Text) -> Text -> State [Text] ()
forall at diags.
(HasLocation at, HasDiagnostics diags) =>
FilePath -> at -> Text -> DiagnosticsT diags ()
warn FilePath
file Node (Lexeme Text)
s Text
"if-statement followed by boolean return can be simplified to return"
checkStmts FilePath
file [s :: Node (Lexeme Text)
s@(Fix (IfStmt Node (Lexeme Text)
_ Node (Lexeme Text)
OnlyReturnBool (Just Node (Lexeme Text)
OnlyReturnBool)))] =
FilePath -> Node (Lexeme Text) -> Text -> State [Text] ()
forall at diags.
(HasLocation at, HasDiagnostics diags) =>
FilePath -> at -> Text -> DiagnosticsT diags ()
warn FilePath
file Node (Lexeme Text)
s Text
"if/else with return true/false can be simplified to return"
checkStmts FilePath
file (Node (Lexeme Text)
_:[Node (Lexeme Text)]
ss) = FilePath -> [Node (Lexeme Text)] -> State [Text] ()
checkStmts FilePath
file [Node (Lexeme Text)]
ss
linter :: AstActions (State [Text]) Text
linter :: AstActions (State [Text]) Text
linter = AstActions (State [Text]) Text
forall (f :: * -> *) text. Applicative f => AstActions f text
astActions
{ doNode :: FilePath
-> Node (Lexeme Text) -> State [Text] () -> State [Text] ()
doNode = \FilePath
file Node (Lexeme Text)
node State [Text] ()
act ->
case Node (Lexeme Text) -> NodeF (Lexeme Text) (Node (Lexeme Text))
forall (f :: * -> *). Fix f -> f (Fix f)
unFix Node (Lexeme Text)
node of
BinaryExpr (Fix (LiteralExpr LiteralType
Bool Lexeme Text
_)) BinaryOp
_ Node (Lexeme Text)
_ -> FilePath -> Node (Lexeme Text) -> Text -> State [Text] ()
forall at diags.
(HasLocation at, HasDiagnostics diags) =>
FilePath -> at -> Text -> DiagnosticsT diags ()
warn FilePath
file Node (Lexeme Text)
node Text
message
BinaryExpr Node (Lexeme Text)
_ BinaryOp
_ (Fix (LiteralExpr LiteralType
Bool Lexeme Text
_)) -> FilePath -> Node (Lexeme Text) -> Text -> State [Text] ()
forall at diags.
(HasLocation at, HasDiagnostics diags) =>
FilePath -> at -> Text -> DiagnosticsT diags ()
warn FilePath
file Node (Lexeme Text)
node Text
message
CompoundStmt [Node (Lexeme Text)]
stmts -> do
FilePath -> [Node (Lexeme Text)] -> State [Text] ()
checkStmts FilePath
file [Node (Lexeme Text)]
stmts
State [Text] ()
act
NodeF (Lexeme Text) (Node (Lexeme Text))
_ -> State [Text] ()
act
}
where
message :: Text
message = Text
"boolean constants should not appear in binary expressions (use ! for negation)"
analyse :: (FilePath, [Node (Lexeme Text)]) -> [Text]
analyse :: (FilePath, [Node (Lexeme Text)]) -> [Text]
analyse = [Text] -> [Text]
forall a. [a] -> [a]
reverse ([Text] -> [Text])
-> ((FilePath, [Node (Lexeme Text)]) -> [Text])
-> (FilePath, [Node (Lexeme Text)])
-> [Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (State [Text] () -> [Text] -> [Text])
-> [Text] -> State [Text] () -> [Text]
forall a b c. (a -> b -> c) -> b -> a -> c
flip State [Text] () -> [Text] -> [Text]
forall s a. State s a -> s -> s
State.execState [] (State [Text] () -> [Text])
-> ((FilePath, [Node (Lexeme Text)]) -> State [Text] ())
-> (FilePath, [Node (Lexeme Text)])
-> [Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AstActions (State [Text]) Text
-> (FilePath, [Node (Lexeme Text)]) -> State [Text] ()
forall text a (f :: * -> *).
(TraverseAst text a, Applicative f) =>
AstActions f text -> a -> f ()
traverseAst AstActions (State [Text]) Text
linter
descr :: ((FilePath, [Node (Lexeme Text)]) -> [Text], (Text, Text))
descr :: ((FilePath, [Node (Lexeme Text)]) -> [Text], (Text, Text))
descr = ((FilePath, [Node (Lexeme Text)]) -> [Text]
analyse, (Text
"booleans", [Text] -> Text
Text.unlines
[ Text
"Checks for if/else statements that return true/false and could be simplified to"
, Text
"just return. E.g.:"
, Text
""
, Text
"```cpp"
, Text
"bool foo(void) {"
, Text
" if (check_something()) {"
, Text
" return false;"
, Text
" }"
, Text
" return true;"
, Text
"}"
, Text
"```"
, Text
""
, Text
"could be simplified to:"
, Text
""
, Text
"```cpp"
, Text
"bool foo(void) {"
, Text
" return !check_something();"
, Text
"}"
, Text
"```"
, Text
""
, Text
"Also checks for the use of `true` or `false` in binary expressions. E.g."
, Text
"`a == true` should be `a` and `a != true` should be `!a`."
, Text
""
, Text
"**Reason:** simpler code is easier to read."
]))