summaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
authorVidar Holen <vidar@vidarholen.net>2023-10-08 18:16:09 -0700
committerVidar Holen <vidar@vidarholen.net>2023-10-08 18:16:09 -0700
commitc9b8ad3439d0496b3df43fcbc2f29e180df2577f (patch)
tree29320d60a1aa783f56a5731208238d9bd9e072f8
parente59fbfebda5cc9e204cf9b72014391f5e0d3961a (diff)
Drop attoparsec/text dependenciesebuild
-rw-r--r--ShellCheck.cabal6
-rw-r--r--src/ShellCheck/PortageVariables.hs159
2 files changed, 50 insertions, 115 deletions
diff --git a/ShellCheck.cabal b/ShellCheck.cabal
index f94952e..3166777 100644
--- a/ShellCheck.cabal
+++ b/ShellCheck.cabal
@@ -66,11 +66,7 @@ library
directory >= 1.2.3 && < 1.4,
-- When cabal supports it, move this to setup-depends:
- process,
-
- -- support for scanning Gentoo eclasses
- attoparsec,
- text
+ process
exposed-modules:
ShellCheck.AST
ShellCheck.ASTLib
diff --git a/src/ShellCheck/PortageVariables.hs b/src/ShellCheck/PortageVariables.hs
index 54b8c1f..e787051 100644
--- a/src/ShellCheck/PortageVariables.hs
+++ b/src/ShellCheck/PortageVariables.hs
@@ -7,34 +7,24 @@ module ShellCheck.PortageVariables (
readPortageVariables
) where
-import Control.Applicative
-import Control.Exception (bracket)
+import ShellCheck.Regex
+
+import Control.Exception
import Control.Monad
-import Control.Monad.Trans.Class (lift)
-import Control.Monad.Trans.Maybe
-import Data.Attoparsec.ByteString
-import qualified Data.Attoparsec.ByteString as A
-import Data.Attoparsec.ByteString.Char8 hiding (takeWhile)
-import Data.ByteString (ByteString)
-import qualified Data.ByteString as B
-import Data.Char (ord)
-import qualified Data.Map as M
-import Data.Maybe (fromJust)
-import qualified Data.Text as T
-import qualified Data.Text.Encoding as T
-import qualified Data.Text.Encoding.Error as T
+import Data.Maybe
import System.Directory (listDirectory)
import System.Exit (ExitCode(..))
import System.FilePath
-import System.IO (hClose)
+import System.IO
import System.Process
-import Prelude hiding (takeWhile)
+import qualified Data.ByteString as B
+import qualified Data.Map as M
-type RepoName = ByteString
-type RepoPath = ByteString
+type RepoName = String
+type RepoPath = String
type EclassName = String
-type EclassVar = ByteString
+type EclassVar = String
-- | This is used for looking up what eclass variables are inherited,
-- keyed by the name of the eclass.
@@ -52,7 +42,7 @@ data Eclass = Eclass
} deriving (Show, Eq, Ord)
readPortageVariables :: IO (M.Map String [String])
-readPortageVariables = M.map (map decodeLenient) <$> portageVariables <$> scanRepos
+readPortageVariables = portageVariables <$> scanRepos
-- | Map from eclass names to a list of eclass variables
portageVariables :: [Repository] -> EclassMap
@@ -67,57 +57,21 @@ scanRepos = do
let cmd = "portageq"
let args = ["repos_config", "/"]
out <- runOrDie cmd args
- case parseOnly reposParser out of
- Left pe -> fail $ show pe
- Right nps -> do
- forM nps $ \(n,p) -> Repository n p <$> getEclasses p
+ forM (reposParser $ lines out) $ \(n,p) -> Repository n p <$> getEclasses p
-- | Get the name of the repo and its path from blocks outputted by
-- @portageq@. If the path doesn't exist, this will return @Nothing@.
-reposParser :: Parser [(RepoName, RepoPath)]
-reposParser =
- choice
- [ [] <$ endOfInput
- , repoName >>= repoBlock
- ]
+reposParser :: [String] -> [(RepoName, RepoPath)]
+reposParser = f ""
where
- -- Get the name of the repo at the top of the block
- repoName :: Parser RepoName
- repoName = do
- _ <- char '['
- n <- takeWhile (/= fromIntegral (ord ']'))
- _ <- char ']'
- _ <- endOfLine
- pure n
-
- -- Parse the block for location field
- repoBlock :: RepoName -> Parser [(RepoName, RepoPath)]
- repoBlock n = choice
- [ do
- l <- "location = " *> takeLine
- -- Found the location, skip the rest of the block
- skipMany miscLine *> endOfBlock
- insert (n,l)
- -- Did not find the location, keep trying
- , miscLine *> repoBlock n
- -- Reached the end of the block, no location field
- , endOfBlock *> ignore
- ]
-
- miscLine :: Parser ()
- miscLine = skipNonEmptyLine
-
- -- A block either ends with an empty line or eof
- endOfBlock :: Parser ()
- endOfBlock = endOfLine <|> endOfInput
-
- -- cons the repo and continue parsing
- insert :: (RepoName, RepoPath) -> Parser [(RepoName, RepoPath)]
- insert r = (r:) <$> reposParser
-
- -- skip the repo and continue parsing
- ignore :: Parser [(RepoName, RepoPath)]
- ignore = reposParser
+ segmentRegex = mkRegex "^\\[(.*)\\].*"
+ locationRegex = mkRegex "^[[:space:]]*location[[:space:]]*=[[:space:]]*(.*)[[:space:]]*$"
+ f name [] = []
+ f name (line:rest) =
+ case (matchRegex segmentRegex line, matchRegex locationRegex line) of
+ (Just [next], _) -> f next rest
+ (_, Just [location]) -> (name, location) : f name rest
+ _ -> f name rest
-- | Scan the repo path for @*.eclass@ files in @eclass/@, then run
-- 'eclassParser' on each of them to produce @[Eclass]@.
@@ -125,56 +79,38 @@ reposParser =
-- If the @eclass/@ directory doesn't exist, the scan is skipped for that
-- repo.
getEclasses :: RepoPath -> IO [Eclass]
-getEclasses repoLoc = fmap (maybe [] id) $ runMaybeT $ do
- let eclassDir = (decodeLenient repoLoc) </> "eclass"
+getEclasses repoLoc = do
+ let eclassDir = repoLoc </> "eclass"
- -- Silently fail if the repo doesn't have an eclass dir
- fs <- MaybeT $ Just <$> listDirectory eclassDir <|> pure Nothing
- let fs' = filter (\(_,e) -> e == ".eclass") $ map splitExtensions fs
+ files <- handle catcher $ listDirectory eclassDir
+ let names = filter (\(_, e) -> e == ".eclass") $ map splitExtension files
- forM fs' $ \(n,e) -> do
- evs <- lift $ parseFromFile eclassParser (eclassDir </> n <.> e)
- case evs of
- Left pe -> lift $ fail $ show pe
- Right vs -> pure $ Eclass n vs
+ forM (names :: [(String, String)]) $ \(name, ext) -> do
+ contents <- withFile (eclassDir </> name <.> ext) ReadMode readFully
+ return $ Eclass name $ eclassParser (lines contents)
+
+ where
+ catcher :: IOException -> IO [String]
+ catcher e = do
+ hPutStrLn stderr $ "Unable to find .eclass files: " ++ show e
+ return []
-- | Scan a @.eclass@ file for any @@@ECLASS_VARIABLE:@ comments, generating
-- a list of eclass variables.
-eclassParser :: Parser [EclassVar]
-eclassParser = choice
- [ -- cons the EclassVar to the list and continue
- liftA2 (:) eclassVar eclassParser
- -- or skip the line and continue
- , skipLine *> eclassParser
- -- or end the list on eof
- , [] <$ endOfInput
- ]
+eclassParser :: [String] -> [String]
+eclassParser lines = mapMaybe match lines
where
- -- Scans for @ECLASS_VARIABLE comments rather than parsing the raw bash
- eclassVar :: Parser EclassVar
- eclassVar = "# @ECLASS_VARIABLE: " *> takeLine
-
-takeLine :: Parser ByteString
-takeLine = A.takeWhile (not . isEndOfLine) <* endOfLine
-
--- | Fails if next char is 'endOfLine'
-skipNonEmptyLine :: Parser ()
-skipNonEmptyLine = A.satisfy (not . isEndOfLine) *> skipLine
-
-skipLine :: Parser ()
-skipLine = A.skipWhile (not . isEndOfLine) <* endOfLine
-
-parseFromFile :: Parser a -> FilePath -> IO (Either String a)
-parseFromFile p = fmap (parseOnly p) . B.readFile
+ varRegex = mkRegex "^[[:space:]]*#[[:space:]]*@ECLASS_VARIABLE:[[:space:]]*([^[:space:]]*)[[:space:]]*$"
+ match str = head <$> matchRegex varRegex str
-- | Run the command and return the full stdout string (stdin is ignored).
--
-- If the command exits with a non-zero exit code, this will throw an
-- error including the captured contents of stdout and stderr.
-runOrDie :: FilePath -> [String] -> IO ByteString
+runOrDie :: FilePath -> [String] -> IO String
runOrDie cmd args = bracket acquire release $ \(_,o,e,p) -> do
- ot <- B.hGetContents (fromJust o)
- et <- B.hGetContents (fromJust e)
+ ot <- readFully (fromJust o)
+ et <- readFully (fromJust e)
ec <- waitForProcess p
case ec of
ExitSuccess -> pure ot
@@ -182,8 +118,8 @@ runOrDie cmd args = bracket acquire release $ \(_,o,e,p) -> do
$ [ [ show cmd ]
++ map show args
++ [ "failed with exit code", show i]
- , [ "stdout:" ], [ decodeLenient ot ]
- , [ "stderr:" ], [ decodeLenient et ]
+ , [ "stdout:" ], [ ot ]
+ , [ "stderr:" ], [ et ]
]
where
acquire = createProcess (proc cmd args)
@@ -195,5 +131,8 @@ runOrDie cmd args = bracket acquire release $ \(_,o,e,p) -> do
_ <- waitForProcess p
forM_ [i,o,e] $ mapM_ hClose
-decodeLenient :: ByteString -> String
-decodeLenient = T.unpack . T.decodeUtf8With T.lenientDecode
+readFully :: Handle -> IO String
+readFully handle = do
+ hSetBinaryMode handle True
+ str <- hGetContents handle
+ length str `seq` return str