{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE Strict #-} module Tokstyle.Linter.MemcpyStructs (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 Language.Cimple.Diagnostics (warn) import Language.Cimple.Pretty (showNode) import Language.Cimple.TraverseAst (AstActions, astActions, doNode, traverseAst) exemptions :: [Text] exemptions :: [Text] exemptions = [ Text "IP_Port" , Text "IP4" , Text "IP6" ] checkSize :: Text -> Text -> FilePath -> Node (Lexeme Text) -> State [Text] () checkSize :: Text -> Text -> FilePath -> Node (Lexeme Text) -> State [Text] () checkSize Text fname Text instead FilePath file Node (Lexeme Text) size = case Node (Lexeme Text) -> NodeF (Lexeme Text) (Node (Lexeme Text)) forall (f :: * -> *). Fix f -> f (Fix f) unFix Node (Lexeme Text) size of SizeofType ty :: Node (Lexeme Text) ty@(Fix (TyUserDefined (L AlexPosn _ LexemeClass _ Text name))) | Text name Text -> [Text] -> Bool forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool `notElem` [Text] exemptions -> 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) size (Text -> State [Text] ()) -> Text -> State [Text] () forall a b. (a -> b) -> a -> b $ Text "`" Text -> Text -> Text forall a. Semigroup a => a -> a -> a <> Text fname Text -> Text -> Text forall a. Semigroup a => a -> a -> a <> Text "` should not be used for structs like `" Text -> Text -> Text forall a. Semigroup a => a -> a -> a <> Node (Lexeme Text) -> Text showNode Node (Lexeme Text) ty Text -> Text -> Text forall a. Semigroup a => a -> a -> a <> Text "`; use " Text -> Text -> Text forall a. Semigroup a => a -> a -> a <> Text instead Text -> Text -> Text forall a. Semigroup a => a -> a -> a <> Text " instead" NodeF (Lexeme Text) (Node (Lexeme Text)) _ -> () -> State [Text] () forall (m :: * -> *) a. Monad m => a -> m a return () 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 (Fix (VarExpr (L AlexPosn _ LexemeClass _ Text "memset"))) [Node (Lexeme Text) _, Node (Lexeme Text) _, Node (Lexeme Text) size] -> Text -> Text -> FilePath -> Node (Lexeme Text) -> State [Text] () checkSize Text "memset" Text "`(Type) {0}`" FilePath file Node (Lexeme Text) size FunctionCall (Fix (VarExpr (L AlexPosn _ LexemeClass _ Text "memcpy"))) [Node (Lexeme Text) _, Node (Lexeme Text) _, Node (Lexeme Text) size] -> Text -> Text -> FilePath -> Node (Lexeme Text) -> State [Text] () checkSize Text "memcpy" Text "assignment" FilePath file Node (Lexeme Text) size 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 "memcpy-structs", [Text] -> Text Text.unlines [ Text "Checks that `memcpy` and `memset` aren't used for struct pointers." , Text "" , Text "Exemptions are:" , Text "" , Text -> [Text] -> Text Text.intercalate Text "\n" ([Text] -> Text) -> ([Text] -> [Text]) -> [Text] -> Text forall b c a. (b -> c) -> (a -> b) -> a -> c . (Text -> Text) -> [Text] -> [Text] forall a b. (a -> b) -> [a] -> [b] map (\Text x -> Text "- `" Text -> Text -> Text forall a. Semigroup a => a -> a -> a <> Text x Text -> Text -> Text forall a. Semigroup a => a -> a -> a <> Text "`") ([Text] -> Text) -> [Text] -> Text forall a b. (a -> b) -> a -> b $ [Text] exemptions , Text "" , Text "**Reason:** structs can contain pointers, so `memset` is risky (it can create" , Text "invalid null pointer representations) and `memcpy` should be replaced by an" , Text "assignment, possibly in a loop, to avoid messing up the size argument of the" , Text "`memcpy` call." ]))