diff --git a/CabalApi.hs b/CabalApi.hs index 0e4d39c..dfdd4a9 100644 --- a/CabalApi.hs +++ b/CabalApi.hs @@ -33,7 +33,7 @@ fromCabalFile :: [GHCOption] fromCabalFile ghcOptions cradle = do cabal <- cabalParseFile cfile case cabalBuildInfo cabal of - Nothing -> throwIO BrokenCabalFile + Nothing -> throwIO $ userError "cabal file is broken" Just binfo -> return $ cookInfo ghcOptions cradle cabal binfo where Just cfile = cradleCabalFile cradle diff --git a/Debug.hs b/Debug.hs index 4ec3c6f..dc02f6f 100644 --- a/Debug.hs +++ b/Debug.hs @@ -1,10 +1,8 @@ - {-# LANGUAGE TemplateHaskell #-} - module Debug (debugInfo, debug) where import CabalApi import Control.Applicative -import Control.Exception.IOChoice.TH +import Control.Exception.IOChoice import Control.Monad import Data.List (intercalate) import Data.Maybe @@ -15,11 +13,6 @@ import Types ---------------------------------------------------------------- -(||>>) :: IO a -> IO a -> IO a -(||>>) = $(newIOChoice [''BrokenCabalFile]) - ----------------------------------------------------------------- - debugInfo :: Options -> Cradle -> String -> String -> IO String debugInfo opt cradle ver fileName = unlines <$> debug opt cradle ver fileName @@ -27,7 +20,7 @@ debug :: Options -> Cradle -> String -> String -> IO [String] debug opt cradle ver fileName = do (gopts, incDir, pkgs) <- if cabal then - fromCabalFile (ghcOpts opt) cradle ||>> return (ghcOpts opt, [], []) + fromCabalFile (ghcOpts opt) cradle ||> return (ghcOpts opt, [], []) else return (ghcOpts opt, [], []) [fast] <- withGHC fileName $ do diff --git a/GHCApi.hs b/GHCApi.hs index 11fccf0..7b8faf1 100644 --- a/GHCApi.hs +++ b/GHCApi.hs @@ -22,6 +22,7 @@ import DynFlags import ErrMsg import Exception import GHC +import GHCChoice import GHC.Paths (libdir) import System.Exit import System.IO @@ -52,7 +53,7 @@ data Build = CabalPkg | SingleFile deriving Eq initializeFlagsWithCradle :: Options -> Cradle -> [GHCOption] -> Bool -> Ghc LogReader initializeFlagsWithCradle opt cradle ghcOptions logging - | cabal = withCabal `gcatch` fallback + | cabal = withCabal ||> withoutCabal | otherwise = withoutCabal where cabal = isJust $ cradleCabalFile cradle @@ -61,8 +62,6 @@ initializeFlagsWithCradle opt cradle ghcOptions logging initSession CabalPkg opt gopts idirs (Just depPkgs) logging withoutCabal = initSession SingleFile opt ghcOptions importDirs Nothing logging - fallback :: BrokenCabalFile -> Ghc LogReader - fallback _ = withoutCabal ---------------------------------------------------------------- diff --git a/Types.hs b/Types.hs index 9408da5..71d1284 100644 --- a/Types.hs +++ b/Types.hs @@ -1,11 +1,7 @@ {-# LANGUAGE FlexibleInstances #-} -{-# LANGUAGE DeriveDataTypeable #-} module Types where -import Control.Exception as E -import Data.Typeable - data OutputStyle = LispStyle | PlainStyle data Options = Options { @@ -82,9 +78,3 @@ type IncludeDir = FilePath type Package = String data CheckSpeed = Slow | Fast - ----------------------------------------------------------------- - -data BrokenCabalFile = BrokenCabalFile deriving (Show, Typeable) - -instance Exception BrokenCabalFile