{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE Strict #-} module Tokstyle.Linter.TypedefName (descr) where import Control.Applicative ((<|>)) import Control.Monad.State.Strict (State) import qualified Control.Monad.State.Strict as State import Data.Fix (Fix (..)) import Data.Maybe (fromMaybe) import Data.Text (Text) import qualified Data.Text as Text import Language.Cimple (Lexeme (..), Node, NodeF (..), lexemeText) import Language.Cimple.Diagnostics (warn) import Language.Cimple.TraverseAst (AstActions, astActions, doNode, traverseAst) valid :: Lexeme Text -> Lexeme Text -> Bool valid :: Lexeme Text -> Lexeme Text -> Bool valid (L AlexPosn _ LexemeClass _ Text tname) (L AlexPosn _ LexemeClass _ Text sname) = Text sname Text -> Text -> Bool forall a. Eq a => a -> a -> Bool == Text tname Bool -> Bool -> Bool || Bool -> Maybe Bool -> Bool forall a. a -> Maybe a -> a fromMaybe Bool False (do Text t <- Text -> Text -> Maybe Text Text.stripSuffix Text "_t" Text tname Text s <- Text -> Text -> Maybe Text Text.stripSuffix Text "_s" Text sname Maybe Text -> Maybe Text -> Maybe Text forall (f :: * -> *) a. Alternative f => f a -> f a -> f a <|> Text -> Text -> Maybe Text Text.stripSuffix Text "_u" Text sname Maybe Text -> Maybe Text -> Maybe Text forall (f :: * -> *) a. Alternative f => f a -> f a -> f a <|> Text -> Text -> Maybe Text Text.stripSuffix Text "_e" Text sname Bool -> Maybe Bool forall (m :: * -> *) a. Monad m => a -> m a return (Bool -> Maybe Bool) -> Bool -> Maybe Bool forall a b. (a -> b) -> a -> b $ Text t Text -> Text -> Bool forall a. Eq a => a -> a -> Bool == Text s) 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 Typedef (Fix (TyStruct Lexeme Text sname)) Lexeme Text tname | Bool -> Bool not (Bool -> Bool) -> Bool -> Bool forall a b. (a -> b) -> a -> b $ Lexeme Text -> Lexeme Text -> Bool valid Lexeme Text tname Lexeme Text sname -> FilePath -> Lexeme Text -> Text -> State [Text] () forall at diags. (HasLocation at, HasDiagnostics diags) => FilePath -> at -> Text -> DiagnosticsT diags () warn FilePath file Lexeme Text sname (Text -> State [Text] ()) -> Text -> State [Text] () forall a b. (a -> b) -> a -> b $ Text -> Lexeme Text -> Lexeme Text -> Text forall a. (Semigroup a, IsString a) => a -> Lexeme a -> Lexeme a -> a warning Text "struct" Lexeme Text tname Lexeme Text sname Typedef (Fix (Struct Lexeme Text sname [Node (Lexeme Text)] _)) Lexeme Text tname | Bool -> Bool not (Bool -> Bool) -> Bool -> Bool forall a b. (a -> b) -> a -> b $ Lexeme Text -> Lexeme Text -> Bool valid Lexeme Text tname Lexeme Text sname -> FilePath -> Lexeme Text -> Text -> State [Text] () forall at diags. (HasLocation at, HasDiagnostics diags) => FilePath -> at -> Text -> DiagnosticsT diags () warn FilePath file Lexeme Text sname (Text -> State [Text] ()) -> Text -> State [Text] () forall a b. (a -> b) -> a -> b $ Text -> Lexeme Text -> Lexeme Text -> Text forall a. (Semigroup a, IsString a) => a -> Lexeme a -> Lexeme a -> a warning Text "struct" Lexeme Text tname Lexeme Text sname Typedef (Fix (Union Lexeme Text uname [Node (Lexeme Text)] _)) Lexeme Text tname | Bool -> Bool not (Bool -> Bool) -> Bool -> Bool forall a b. (a -> b) -> a -> b $ Lexeme Text -> Lexeme Text -> Bool valid Lexeme Text tname Lexeme Text uname -> FilePath -> Lexeme Text -> Text -> State [Text] () forall at diags. (HasLocation at, HasDiagnostics diags) => FilePath -> at -> Text -> DiagnosticsT diags () warn FilePath file Lexeme Text uname (Text -> State [Text] ()) -> Text -> State [Text] () forall a b. (a -> b) -> a -> b $ Text -> Lexeme Text -> Lexeme Text -> Text forall a. (Semigroup a, IsString a) => a -> Lexeme a -> Lexeme a -> a warning Text "union" Lexeme Text tname Lexeme Text uname EnumDecl Lexeme Text ename [Node (Lexeme Text)] _ Lexeme Text tname | Bool -> Bool not (Bool -> Bool) -> Bool -> Bool forall a b. (a -> b) -> a -> b $ Lexeme Text -> Lexeme Text -> Bool valid Lexeme Text tname Lexeme Text ename -> FilePath -> Lexeme Text -> Text -> State [Text] () forall at diags. (HasLocation at, HasDiagnostics diags) => FilePath -> at -> Text -> DiagnosticsT diags () warn FilePath file Lexeme Text ename (Text -> State [Text] ()) -> Text -> State [Text] () forall a b. (a -> b) -> a -> b $ Text -> Lexeme Text -> Lexeme Text -> Text forall a. (Semigroup a, IsString a) => a -> Lexeme a -> Lexeme a -> a warning Text "union" Lexeme Text tname Lexeme Text ename FunctionDefn{} -> () -> State [Text] () forall (m :: * -> *) a. Monad m => a -> m a return () NodeF (Lexeme Text) (Node (Lexeme Text)) _ -> State [Text] () act } where warning :: a -> Lexeme a -> Lexeme a -> a warning a tag Lexeme a tname Lexeme a name = a "typedef name `" a -> a -> a forall a. Semigroup a => a -> a -> a <> Lexeme a -> a forall text. Lexeme text -> text lexemeText Lexeme a tname a -> a -> a forall a. Semigroup a => a -> a -> a <> a "` does not match " a -> a -> a forall a. Semigroup a => a -> a -> a <> a tag a -> a -> a forall a. Semigroup a => a -> a -> a <> a " name `" a -> a -> a forall a. Semigroup a => a -> a -> a <> Lexeme a -> a forall text. Lexeme text -> text lexemeText Lexeme a name a -> a -> a forall a. Semigroup a => a -> a -> a <> a "`" 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 "typedef-name", [Text] -> Text Text.unlines [ Text "Checks that typedef names match the struct/union name. E.g." , Text "`typedef struct Foo_ { ... } Foo;` should instead be" , Text "`typedef struct Foo { ... } Foo;`." , Text "" , Text "**Reason:** there is no good reason for them to be different, and it adds" , Text "confusion and a potential for C++ code to pick the wrong name and later break" , Text "in refactorings." ]))