[commit: ghc] master: Split off a InteractiveEvalTypes module to remove an import loop (575cb0c)
Ian Lynagh
igloo at earth.li
Sat Apr 6 21:37:08 CEST 2013
Repository : http://darcs.haskell.org/ghc.git/
On branch : master
https://github.com/ghc/ghc/commit/575cb0c35f712980ad0bcb2283c1fd9332861cf2
>---------------------------------------------------------------
commit 575cb0c35f712980ad0bcb2283c1fd9332861cf2
Author: Ian Lynagh <ian at well-typed.com>
Date: Sat Apr 6 13:20:02 2013 +0100
Split off a InteractiveEvalTypes module to remove an import loop
>---------------------------------------------------------------
compiler/ghc.cabal.in | 1 +
compiler/main/HscTypes.lhs | 2 +-
compiler/main/InteractiveEval.hs | 40 ++-------------------
compiler/main/InteractiveEval.hs-boot | 3 --
compiler/main/InteractiveEvalTypes.hs | 65 +++++++++++++++++++++++++++++++++++
5 files changed, 69 insertions(+), 42 deletions(-)
diff --git a/compiler/ghc.cabal.in b/compiler/ghc.cabal.in
index cf105a0..749665b 100644
--- a/compiler/ghc.cabal.in
+++ b/compiler/ghc.cabal.in
@@ -288,6 +288,7 @@ Library
HscStats
HscTypes
InteractiveEval
+ InteractiveEvalTypes
PackageConfig
Packages
PlatformConstants
diff --git a/compiler/main/HscTypes.lhs b/compiler/main/HscTypes.lhs
index 9c1648c..d9fe88b 100644
--- a/compiler/main/HscTypes.lhs
+++ b/compiler/main/HscTypes.lhs
@@ -114,7 +114,7 @@ module HscTypes (
#ifdef GHCI
import ByteCodeAsm ( CompiledByteCode )
-import {-# SOURCE #-} InteractiveEval ( Resume )
+import InteractiveEvalTypes ( Resume )
#endif
import HsSyn
diff --git a/compiler/main/InteractiveEval.hs b/compiler/main/InteractiveEval.hs
index d0c1305..391de5a 100644
--- a/compiler/main/InteractiveEval.hs
+++ b/compiler/main/InteractiveEval.hs
@@ -38,6 +38,8 @@ module InteractiveEval (
#include "HsVersions.h"
+import InteractiveEvalTypes
+
import GhcMonad
import HscMain
import HsSyn
@@ -89,37 +91,6 @@ import System.IO.Unsafe
-- -----------------------------------------------------------------------------
-- running a statement interactively
-data RunResult
- = RunOk [Name] -- ^ names bound by this evaluation
- | RunException SomeException -- ^ statement raised an exception
- | RunBreak ThreadId [Name] (Maybe BreakInfo)
-
-data Status
- = Break Bool HValue BreakInfo ThreadId
- -- ^ the computation hit a breakpoint (Bool <=> was an exception)
- | Complete (Either SomeException [HValue])
- -- ^ the computation completed with either an exception or a value
-
-data Resume
- = Resume {
- resumeStmt :: String, -- the original statement
- resumeThreadId :: ThreadId, -- thread running the computation
- resumeBreakMVar :: MVar (),
- resumeStatMVar :: MVar Status,
- resumeBindings :: ([TyThing], GlobalRdrEnv),
- resumeFinalIds :: [Id], -- [Id] to bind on completion
- resumeApStack :: HValue, -- The object from which we can get
- -- value of the free variables.
- resumeBreakInfo :: Maybe BreakInfo,
- -- the breakpoint we stopped at
- -- (Nothing <=> exception)
- resumeSpan :: SrcSpan, -- just a cache, otherwise it's a pain
- -- to fetch the ModDetails & ModBreaks
- -- to get this.
- resumeHistory :: [History],
- resumeHistoryIx :: Int -- 0 <==> at the top of the history
- }
-
getResumeContext :: GhcMonad m => m [Resume]
getResumeContext = withSession (return . ic_resume . hsc_IC)
@@ -132,13 +103,6 @@ isStep :: SingleStep -> Bool
isStep RunToCompletion = False
isStep _ = True
-data History
- = History {
- historyApStack :: HValue,
- historyBreakInfo :: BreakInfo,
- historyEnclosingDecls :: [String] -- declarations enclosing the breakpoint
- }
-
mkHistory :: HscEnv -> HValue -> BreakInfo -> History
mkHistory hsc_env hval bi = let
decls = findEnclosingDecls hsc_env bi
diff --git a/compiler/main/InteractiveEval.hs-boot b/compiler/main/InteractiveEval.hs-boot
deleted file mode 100644
index 67b7743..0000000
--- a/compiler/main/InteractiveEval.hs-boot
+++ /dev/null
@@ -1,3 +0,0 @@
-module InteractiveEval (Resume) where
-
-data Resume
diff --git a/compiler/main/InteractiveEvalTypes.hs b/compiler/main/InteractiveEvalTypes.hs
new file mode 100644
index 0000000..87027cf
--- /dev/null
+++ b/compiler/main/InteractiveEvalTypes.hs
@@ -0,0 +1,65 @@
+-- -----------------------------------------------------------------------------
+--
+-- (c) The University of Glasgow, 2005-2007
+--
+-- Running statements interactively
+--
+-- -----------------------------------------------------------------------------
+
+module InteractiveEvalTypes (
+#ifdef GHCI
+ RunResult(..), Status(..), Resume(..), History(..),
+#endif
+ ) where
+
+#ifdef GHCI
+
+import Id
+import Name
+import RdrName
+import TypeRep
+import ByteCodeInstr
+import ByteCodeLink
+import SrcLoc
+import Exception
+import Control.Concurrent
+
+data RunResult
+ = RunOk [Name] -- ^ names bound by this evaluation
+ | RunException SomeException -- ^ statement raised an exception
+ | RunBreak ThreadId [Name] (Maybe BreakInfo)
+
+data Status
+ = Break Bool HValue BreakInfo ThreadId
+ -- ^ the computation hit a breakpoint (Bool <=> was an exception)
+ | Complete (Either SomeException [HValue])
+ -- ^ the computation completed with either an exception or a value
+
+data Resume
+ = Resume {
+ resumeStmt :: String, -- the original statement
+ resumeThreadId :: ThreadId, -- thread running the computation
+ resumeBreakMVar :: MVar (),
+ resumeStatMVar :: MVar Status,
+ resumeBindings :: ([TyThing], GlobalRdrEnv),
+ resumeFinalIds :: [Id], -- [Id] to bind on completion
+ resumeApStack :: HValue, -- The object from which we can get
+ -- value of the free variables.
+ resumeBreakInfo :: Maybe BreakInfo,
+ -- the breakpoint we stopped at
+ -- (Nothing <=> exception)
+ resumeSpan :: SrcSpan, -- just a cache, otherwise it's a pain
+ -- to fetch the ModDetails & ModBreaks
+ -- to get this.
+ resumeHistory :: [History],
+ resumeHistoryIx :: Int -- 0 <==> at the top of the history
+ }
+
+data History
+ = History {
+ historyApStack :: HValue,
+ historyBreakInfo :: BreakInfo,
+ historyEnclosingDecls :: [String] -- declarations enclosing the breakpoint
+ }
+#endif
+
More information about the ghc-commits
mailing list