@@ -5,21 +5,25 @@ module Main where
55import CC.Analyze
66import CC.Types
77import Data.Aeson
8+ import Data.Attoparsec.ByteString.Lazy
9+ import qualified Data.ByteString as BS
810import qualified Data.ByteString.Lazy as BSL
911import qualified Data.Map.Strict as DM
1012import Data.Maybe
1113import Data.Monoid
14+ import Data.Word
1215import qualified Data.Yaml as YML
1316import System.Directory
1417import System.FilePath.Glob
18+ import System.FilePath.Posix
1519
1620--------------------------------------------------------------------------------
1721
1822main :: IO ()
1923main = do
2024 config <- loadConfig " /config.json"
2125 env <- fromMaybe DM. empty <$> YML. decodeFile " data/mapping.yml"
22- paths <- shFiles $! _include_paths config
26+ paths <- shellScripts $! _include_paths config
2327 issues <- analyzeFiles env paths
2428 mapM_ printIssue issues
2529
@@ -38,9 +42,83 @@ printIssue = BSL.putStr . (<> "\0") . encode
3842
3943--------------------------------------------------------------------------------
4044
41- shFiles :: [FilePath ] -> IO [FilePath ]
42- shFiles paths =
45+ shellScripts :: [FilePath ] -> IO [FilePath ]
46+ shellScripts paths =
4347 fmap concat $! sequence $! fmap (matched . globDir [compile " **/*.sh" ]) paths
4448 where
4549 matched :: Functor f => f ([[a ]], [b ]) -> f [a ]
4650 matched x = (concat . fst ) <$> x
51+
52+ --------------------------------------------------------------------------------
53+
54+ -- | Determines whether a file is a shell script that we can work with.
55+ isShellScript :: FilePath -> IO Bool
56+ isShellScript path =
57+ if hasExtension path
58+ then return hasShellExtension
59+ else do
60+ header <- readHeader
61+ if hasShebang header
62+ then case readShebang header of
63+ Just (Shebang x y) -> return $ hasValidInterpretter x y
64+ Nothing -> return False
65+ else return False
66+ where
67+ ----------------------------------------------------------------------------
68+
69+ carriageReturn :: Word8 -> Bool
70+ carriageReturn = (== 13 )
71+
72+ endOfLine :: Word8 -> Bool
73+ endOfLine x = newline x || carriageReturn x
74+
75+ newline :: Word8 -> Bool
76+ newline = (== 10 )
77+
78+ whitespace :: Word8 -> Bool
79+ whitespace = (== 32 )
80+
81+ ----------------------------------------------------------------------------
82+
83+ whiteList :: [BS. ByteString ]
84+ whiteList = [ " sh"
85+ , " ash"
86+ , " dash"
87+ , " bash"
88+ , " ksh"
89+ ]
90+
91+ ----------------------------------------------------------------------------
92+
93+ hasShebang :: BSL. ByteString -> Bool
94+ hasShebang x = BSL. take 2 x == " #!"
95+
96+ hasShellExtension :: Bool
97+ hasShellExtension = takeExtension path == " .sh"
98+
99+ hasValidInterpretter :: BS. ByteString -> BS. ByteString -> Bool
100+ hasValidInterpretter interpretter arguments =
101+ if BS. isSuffixOf " env" interpretter
102+ then any (`BS.isPrefixOf` arguments) whiteList
103+ else any (`BS.isSuffixOf` interpretter) whiteList
104+
105+ ----------------------------------------------------------------------------
106+
107+ readHeader :: IO BSL. ByteString
108+ readHeader = do
109+ contents <- BSL. readFile path
110+ return $ BSL. takeWhile (not . endOfLine) contents
111+
112+ readShebang :: BSL. ByteString -> Maybe Shebang
113+ readShebang x = maybeResult $ parse shebang x
114+
115+ ----------------------------------------------------------------------------
116+
117+ shebang :: Parser Shebang
118+ shebang = do
119+ _ <- string " #!"
120+ interpretter <- takeTill whitespace
121+ arguments <- option " " $ do
122+ _ <- string " "
123+ takeTill endOfLine
124+ return $ Shebang interpretter arguments
0 commit comments