Commit b88d0c74 authored by Andrew Gibiansky's avatar Andrew Gibiansky

adding checks for broken packages

parent a741c62b
...@@ -101,6 +101,7 @@ library ...@@ -101,6 +101,7 @@ library
IHaskell.IPython IHaskell.IPython
IHaskell.Flags IHaskell.Flags
IHaskell.Types IHaskell.Types
IHaskell.BrokenPackages
other-modules: other-modules:
Paths_ihaskell Paths_ihaskell
...@@ -125,6 +126,7 @@ executable IHaskell ...@@ -125,6 +126,7 @@ executable IHaskell
IHaskell.Flags IHaskell.Flags
IHaskell.Types IHaskell.Types
IHaskell.Display IHaskell.Display
IHaskell.BrokenPackages
default-extensions: DoAndIfThenElse default-extensions: DoAndIfThenElse
......
{-# 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"
...@@ -68,6 +68,7 @@ import IHaskell.Eval.Lint ...@@ -68,6 +68,7 @@ import IHaskell.Eval.Lint
import IHaskell.Display import IHaskell.Display
import qualified IHaskell.Eval.Hoogle as Hoogle import qualified IHaskell.Eval.Hoogle as Hoogle
import IHaskell.Eval.Util import IHaskell.Eval.Util
import IHaskell.BrokenPackages
import Paths_ihaskell (version) import Paths_ihaskell (version)
import Data.Version (versionBranch) import Data.Version (versionBranch)
...@@ -148,6 +149,7 @@ initializeImports = do ...@@ -148,6 +149,7 @@ initializeImports = do
-- XXX this will try to load broken packages, provided they depend -- XXX this will try to load broken packages, provided they depend
-- on the right ihaskell version -- on the right ihaskell version
dflags <- getSessionDynFlags dflags <- getSessionDynFlags
broken <- liftIO getBrokenPackages
displayPackages <- liftIO $ do displayPackages <- liftIO $ do
(dflags, _) <- initPackages dflags (dflags, _) <- initPackages dflags
let Just db = pkgDatabase dflags let Just db = pkgDatabase dflags
...@@ -175,6 +177,7 @@ initializeImports = do ...@@ -175,6 +177,7 @@ initializeImports = do
displayPkgs = [ pkgName displayPkgs = [ pkgName
| pkgName <- packageNames, | pkgName <- packageNames,
Just (x:_) <- [stripPrefix initStr pkgName], Just (x:_) <- [stripPrefix initStr pkgName],
pkgName `notElem` broken,
isAlpha x] isAlpha x]
return displayPkgs return displayPkgs
......
...@@ -36,6 +36,8 @@ import Text.ParserCombinators.ReadP ...@@ -36,6 +36,8 @@ import Text.ParserCombinators.ReadP
import IPython.Kernel import IPython.Kernel
data Test = Test
data ViewFormat data ViewFormat
= Pdf = Pdf
| Html | Html
......
Markdown is supported
0% or
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment