diff options
author | Simon Marlow <marlowsd@gmail.com> | 2010-10-27 12:11:32 +0000 |
---|---|---|
committer | Simon Marlow <marlowsd@gmail.com> | 2010-10-27 12:11:32 +0000 |
commit | 94bf0d3604ff0d2ecab246924af712bdd1c29a40 (patch) | |
tree | 6901f70d45e5afdec98c14f8fb61486d5e321e1f /ghc/GhciMonad.hs | |
parent | 2493b18037055a5c284563d10931386e589a79b0 (diff) | |
download | haskell-94bf0d3604ff0d2ecab246924af712bdd1c29a40.tar.gz |
Refactoring and tidyup of HscMain and related things (also fix #1666)
While trying to fix #1666 (-Werror aborts too early) I decided to some
tidyup in GHC/DriverPipeline/HscMain.
- The GhcMonad overloading is gone from DriverPipeline and HscMain
now. GhcMonad is now defined in a module of its own, and only
used in the top-level GHC layer. DriverPipeline and HscMain
use the plain IO monad and take HscEnv as an argument.
- WarnLogMonad is gone. printExceptionAndWarnings is now called
printException (the old name is deprecated). Session no longer
contains warnings.
- HscMain has its own little monad that collects warnings, and also
plumbs HscEnv around. The idea here is that warnings are collected
while we're in HscMain, but on exit from HscMain (any function) we
check for warnings and either print them (via log_action, so IDEs
can still override the printing), or turn them into an error if
-Werror is on.
- GhcApiCallbacks is gone, along with GHC.loadWithLogger. Thomas
Schilling told me he wasn't using these, and I don't see a good
reason to have them.
- there's a new pure API to the parser (suggestion from Neil Mitchell):
parser :: String
-> DynFlags
-> FilePath
-> Either ErrorMessages (WarningMessages,
Located (HsModule RdrName))
Diffstat (limited to 'ghc/GhciMonad.hs')
-rw-r--r-- | ghc/GhciMonad.hs | 16 |
1 files changed, 3 insertions, 13 deletions
diff --git a/ghc/GhciMonad.hs b/ghc/GhciMonad.hs index 5494b4ea4c..82f2aa7c73 100644 --- a/ghc/GhciMonad.hs +++ b/ghc/GhciMonad.hs @@ -14,12 +14,13 @@ module GhciMonad where #include "HsVersions.h" import qualified GHC +import GhcMonad hiding (liftIO) import Outputable hiding (printForUser, printForUserPartWay) import qualified Outputable import Panic hiding (showException) import Util import DynFlags -import HscTypes hiding (liftIO) +import HscTypes import SrcLoc import Module import ObjLink @@ -28,13 +29,10 @@ import StaticFlags import qualified MonadUtils import Exception --- import Data.Maybe import Numeric import Data.Array --- import Data.Char import Data.Int ( Int64 ) import Data.IORef --- import Data.List import System.CPUTime import System.Environment import System.IO @@ -181,10 +179,6 @@ instance GhcMonad (InputT GHCi) where instance MonadUtils.MonadIO (InputT GHCi) where liftIO = Trans.liftIO -instance WarnLogMonad (InputT GHCi) where - setWarnings = lift . setWarnings - getWarnings = lift getWarnings - instance ExceptionMonad GHCi where gcatch m h = GHCi $ \r -> unGHCi m r `gcatch` (\e -> unGHCi (h e) r) gblock (GHCi m) = GHCi $ \r -> gblock (m r) @@ -196,10 +190,6 @@ instance ExceptionMonad GHCi where in unGHCi (f g_restore) s -instance WarnLogMonad GHCi where - setWarnings warns = liftGhc $ setWarnings warns - getWarnings = liftGhc $ getWarnings - instance MonadIO GHCi where liftIO = io @@ -263,7 +253,7 @@ runStmt expr step = do withProgName (progname st) $ withArgs (args st) $ reflectGHCi x $ do - GHC.handleSourceError (\e -> do GHC.printExceptionAndWarnings e + GHC.handleSourceError (\e -> do GHC.printException e return GHC.RunFailed) $ do GHC.runStmt expr step |