adding checks for broken packages

This commit is contained in:
Andrew Gibiansky 2014-02-28 16:19:37 -08:00
parent a741c62b00
commit b88d0c744b
4 changed files with 44 additions and 0 deletions

View File

@ -101,6 +101,7 @@ library
IHaskell.IPython
IHaskell.Flags
IHaskell.Types
IHaskell.BrokenPackages
other-modules:
Paths_ihaskell
@ -125,6 +126,7 @@ executable IHaskell
IHaskell.Flags
IHaskell.Types
IHaskell.Display
IHaskell.BrokenPackages
default-extensions: DoAndIfThenElse

View File

@ -0,0 +1,37 @@
{-# LANGUAGE OverloadedStrings, NoImplicitPrelude #-}
module IHaskell.BrokenPackages (getBrokenPackages) where
import ClassyPrelude hiding ((<|>))
import Text.Parsec
import Text.Parsec.String
import Control.Applicative hiding ((<|>), many)
import Shelly
data BrokenPackage = BrokenPackage {
packageID :: String,
brokenDeps :: [String]
}
instance Show BrokenPackage where
show = packageID
getBrokenPackages :: IO [String]
getBrokenPackages = shellyNoDir $ do
silently $ errExit False $ run "ghc-pkg" ["check"]
checkOut <- lastStderr
return $ case parse (many check) "ghc-pkg output" $ unpack checkOut of
Left err -> []
Right pkgs -> map show pkgs
check :: Parser BrokenPackage
check = string "There are problems in package "
>> BrokenPackage <$> ident <* string ":\n" <*> many1 dependency
ident :: Parser String
ident = many (alphaNum <|> oneOf "-.")
dependency :: Parser String
dependency = string " dependency \"" *> ident <* string "\" doesn't exist\n"

View File

@ -68,6 +68,7 @@ import IHaskell.Eval.Lint
import IHaskell.Display
import qualified IHaskell.Eval.Hoogle as Hoogle
import IHaskell.Eval.Util
import IHaskell.BrokenPackages
import Paths_ihaskell (version)
import Data.Version (versionBranch)
@ -148,6 +149,7 @@ initializeImports = do
-- XXX this will try to load broken packages, provided they depend
-- on the right ihaskell version
dflags <- getSessionDynFlags
broken <- liftIO getBrokenPackages
displayPackages <- liftIO $ do
(dflags, _) <- initPackages dflags
let Just db = pkgDatabase dflags
@ -175,6 +177,7 @@ initializeImports = do
displayPkgs = [ pkgName
| pkgName <- packageNames,
Just (x:_) <- [stripPrefix initStr pkgName],
pkgName `notElem` broken,
isAlpha x]
return displayPkgs

View File

@ -36,6 +36,8 @@ import Text.ParserCombinators.ReadP
import IPython.Kernel
data Test = Test
data ViewFormat
= Pdf
| Html