{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE Strict #-} module Tokstyle.Linter.GlobalFuncs (descr) where 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 (..), Scope (..), lexemeText) import Language.Cimple.Diagnostics (warn) import System.FilePath (takeExtension) analyse :: (FilePath, [Node (Lexeme Text)]) -> [Text] analyse :: (FilePath, [Node (Lexeme Text)]) -> [Text] analyse (FilePath file, [Node (Lexeme Text)] _) | FilePath -> FilePath takeExtension FilePath file FilePath -> FilePath -> Bool forall a. Eq a => a -> a -> Bool /= FilePath ".c" = [] analyse (FilePath file, [Node (Lexeme Text)] ast) = [Text] -> [Text] forall a. [a] -> [a] reverse ([Text] -> [Text]) -> [Text] -> [Text] forall a b. (a -> b) -> a -> b $ State [Text] [()] -> [Text] -> [Text] forall s a. State s a -> s -> s State.execState ((Node (Lexeme Text) -> StateT [Text] Identity ()) -> [Node (Lexeme Text)] -> State [Text] [()] forall (t :: * -> *) (m :: * -> *) a b. (Traversable t, Monad m) => (a -> m b) -> t a -> m (t b) mapM Node (Lexeme Text) -> StateT [Text] Identity () forall diags. HasDiagnostics diags => Node (Lexeme Text) -> DiagnosticsT diags () go [Node (Lexeme Text)] ast) [] where go :: Node (Lexeme Text) -> DiagnosticsT diags () go (Fix (FunctionDecl Scope Global (Fix (FunctionPrototype Node (Lexeme Text) _ Lexeme Text name [Node (Lexeme Text)] _)))) = FilePath -> Lexeme Text -> Text -> DiagnosticsT diags () forall at diags. (HasLocation at, HasDiagnostics diags) => FilePath -> at -> Text -> DiagnosticsT diags () warn FilePath file Lexeme Text name (Text -> DiagnosticsT diags ()) -> Text -> DiagnosticsT diags () forall a b. (a -> b) -> a -> b $ Text "global function `" Text -> Text -> Text forall a. Semigroup a => a -> a -> a <> Lexeme Text -> Text forall text. Lexeme text -> text lexemeText Lexeme Text name Text -> Text -> Text forall a. Semigroup a => a -> a -> a <> Text "` declared in .c file" go Node (Lexeme Text) _ = () -> DiagnosticsT diags () forall (m :: * -> *) a. Monad m => a -> m a return () descr :: ((FilePath, [Node (Lexeme Text)]) -> [Text], (Text, Text)) descr :: ((FilePath, [Node (Lexeme Text)]) -> [Text], (Text, Text)) descr = ((FilePath, [Node (Lexeme Text)]) -> [Text] analyse, (Text "global-funcs", [Text] -> Text Text.unlines [ Text "Checks that no extern functions are declared in .c files." , Text "" , Text "Extern functions must only be declared in .h files. In .c files all declarations" , Text "must be static." , Text "" , Text "**Reason:** extern declarations in .c files mean that we depend on a function" , Text "not declared in a .h file we can include. This means we're depending on an" , Text "unexported implementation detail, and there is no compiler that can check" , Text "whether our declaration matches the implementation's definition." ]))