{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE Strict #-} module Tokstyle.Linter.FuncPrototypes (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, Node, NodeF (..)) import qualified Language.Cimple.Diagnostics as Diagnostics import Language.Cimple.TraverseAst (AstActions, astActions, doNode, traverseAst) 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 FunctionPrototype Node (Lexeme Text) _ Lexeme Text name [] -> 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 "empty parameter list must be written as `(void)`" State [Text] () act FunctionDefn{} -> () -> State [Text] () forall (m :: * -> *) a. Monad m => a -> m a return () NodeF (Lexeme Text) (Node (Lexeme Text)) _ -> State [Text] () act } 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 "func-prototypes", [Text] -> Text Text.unlines [ Text "Checks that empty parameter lists in C functions are written as `(void)`." , Text "" , Text "**Reason:** old-style empty parameter lists written as `()` are risky, because" , Text "C interprets them as variadic. GCC warns about this but sometimes misses one." ]))