{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE Strict #-}
module Tokstyle.Linter.LoggerCalls (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 (String),
Node, NodeF (..))
import qualified Language.Cimple.Diagnostics as Diagnostics
import Language.Cimple.TraverseAst (AstActions, astActions, doNode,
traverseAst)
import System.FilePath (takeFileName)
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
FunctionCall Node (Lexeme Text)
_ (Node (Lexeme Text)
_:Fix (LiteralExpr LiteralType
String Lexeme Text
_):[Node (Lexeme Text)]
_) -> State [Text] ()
act
FunctionCall (Fix (LiteralExpr LiteralType
_ (L AlexPosn
_ LexemeClass
_ Text
"LOGGER_ASSERT"))) (Node (Lexeme Text)
_:Node (Lexeme Text)
_:Fix (LiteralExpr LiteralType
String Lexeme Text
_):[Node (Lexeme Text)]
_) -> State [Text] ()
act
FunctionCall (Fix (LiteralExpr LiteralType
_ name :: Lexeme Text
name@(L AlexPosn
_ LexemeClass
_ Text
func))) [Node (Lexeme Text)]
_ | Text -> Text -> Bool
Text.isPrefixOf Text
"LOGGER_" Text
func -> do
FilePath -> Lexeme Text -> Text -> State [Text] ()
forall at diags.
(HasLocation at, HasDiagnostics diags) =>
FilePath -> at -> Text -> DiagnosticsT diags ()
Diagnostics.warn FilePath
file Lexeme Text
name (Text -> State [Text] ()) -> Text -> State [Text] ()
forall a b. (a -> b) -> a -> b
$ Text
"logger call `" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
func Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"` has a non-literal format argument"
State [Text] ()
act
NodeF (Lexeme Text) (Node (Lexeme Text))
_ -> State [Text] ()
act
}
analyse :: (FilePath, [Node (Lexeme Text)]) -> [Text]
analyse :: (FilePath, [Node (Lexeme Text)]) -> [Text]
analyse (FilePath
file, [Node (Lexeme Text)]
_) | FilePath -> FilePath
takeFileName FilePath
file FilePath -> FilePath -> Bool
forall a. Eq a => a -> a -> Bool
== FilePath
"logger.h" = []
analyse (FilePath, [Node (Lexeme Text)])
tu = [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 ((FilePath, [Node (Lexeme Text)]) -> [Text])
-> (FilePath, [Node (Lexeme Text)]) -> [Text]
forall a b. (a -> b) -> a -> b
$ (FilePath, [Node (Lexeme Text)])
tu
descr :: ((FilePath, [Node (Lexeme Text)]) -> [Text], (Text, Text))
descr :: ((FilePath, [Node (Lexeme Text)]) -> [Text], (Text, Text))
descr = ((FilePath, [Node (Lexeme Text)]) -> [Text]
analyse, (Text
"logger-calls", [Text] -> Text
Text.unlines
[ Text
"Checks that the format argument in LOGGER calls is a string literal."
, Text
""
, Text
"**Reason:** format arguments must always be string literals so they can be"
, Text
"statically checked to match with their argument list."
]))