Skip to content

Commit

Permalink
Split off a InteractiveEvalTypes module to remove an import loop
Browse files Browse the repository at this point in the history
  • Loading branch information
Ian Lynagh committed Apr 6, 2013
1 parent 6534c99 commit 575cb0c
Show file tree
Hide file tree
Showing 5 changed files with 69 additions and 42 deletions.
1 change: 1 addition & 0 deletions compiler/ghc.cabal.in
Expand Up @@ -288,6 +288,7 @@ Library
HscStats
HscTypes
InteractiveEval
InteractiveEvalTypes
PackageConfig
Packages
PlatformConstants
Expand Down
2 changes: 1 addition & 1 deletion compiler/main/HscTypes.lhs
Expand Up @@ -114,7 +114,7 @@ module HscTypes (
#ifdef GHCI
import ByteCodeAsm ( CompiledByteCode )
import {-# SOURCE #-} InteractiveEval ( Resume )
import InteractiveEvalTypes ( Resume )
#endif
import HsSyn
Expand Down
40 changes: 2 additions & 38 deletions compiler/main/InteractiveEval.hs
Expand Up @@ -38,6 +38,8 @@ module InteractiveEval (

#include "HsVersions.h"

import InteractiveEvalTypes

import GhcMonad
import HscMain
import HsSyn
Expand Down Expand Up @@ -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)

Expand All @@ -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
Expand Down
3 changes: 0 additions & 3 deletions compiler/main/InteractiveEval.hs-boot

This file was deleted.

65 changes: 65 additions & 0 deletions 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

0 comments on commit 575cb0c

Please sign in to comment.