@@ -4,10 +4,13 @@ module Main where
44
55import CC.Analyze
66import CC.Types
7+ import Control.Monad
8+ import Control.Monad.Extra
79import Data.Aeson
810import Data.Attoparsec.ByteString.Lazy
911import qualified Data.ByteString as BS
1012import qualified Data.ByteString.Lazy as BSL
13+ import Data.List
1114import qualified Data.Map.Strict as DM
1215import Data.Maybe
1316import Data.Monoid
@@ -33,7 +36,7 @@ loadConfig :: FilePath -> IO Config
3336loadConfig path = do
3437 fileExists <- doesFileExist path
3538 config <- if fileExists then decode <$> BSL. readFile path else return Nothing
36- return $! fromMaybe Config { _include_paths = [" ." ] } config
39+ return $! fromMaybe Config { _include_paths = [" ./ " ] } config
3740
3841--------------------------------------------------------------------------------
3942
@@ -43,11 +46,23 @@ printIssue = BSL.putStr . (<> "\0") . encode
4346--------------------------------------------------------------------------------
4447
4548shellScripts :: [FilePath ] -> IO [FilePath ]
46- shellScripts paths =
47- fmap concat $! sequence $! fmap (matched . globDir [compile " **/*.sh" ]) paths
49+ shellScripts paths = do
50+ dotShFiles <- concat . fst <$> globDir patterns " ."
51+ otherFiles <- return files
52+ allScripts <- filterM validateScript $ dotShFiles ++ otherFiles
53+ return $ fmap clean allScripts
4854 where
49- matched :: Functor f => f ([[a ]], [b ]) -> f [a ]
50- matched x = (concat . fst ) <$> x
55+ (dirs, files) = partition hasTrailingPathSeparator paths
56+
57+ clean :: String -> String
58+ clean (' .' : ' /' : x) = x
59+ clean x = x
60+
61+ patterns :: [Pattern ]
62+ patterns = fmap (compile . (++ " **/*.sh" )) dirs
63+
64+ validateScript :: FilePath -> IO Bool
65+ validateScript x = doesFileExist x &&^ isShellScript x
5166
5267--------------------------------------------------------------------------------
5368
@@ -119,6 +134,6 @@ isShellScript path =
119134 _ <- string " #!"
120135 interpretter <- takeTill whitespace
121136 arguments <- option " " $ do
122- _ <- string " "
137+ _ <- string " "
123138 takeTill endOfLine
124139 return $ Shebang interpretter arguments
0 commit comments