[commit: ghc] master: Remove deprecated InteractiveEval API (eee8199)

git at git.haskell.org git at git.haskell.org
Tue Jan 10 19:22:22 UTC 2017


Repository : ssh://git@git.haskell.org/ghc

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/eee819943a0ea05af369fe3c728b865094e8fe33/ghc

>---------------------------------------------------------------

commit eee819943a0ea05af369fe3c728b865094e8fe33
Author: David Feuer <david.feuer at gmail.com>
Date:   Tue Jan 10 13:40:51 2017 -0500

    Remove deprecated InteractiveEval API
    
    Remove `RunResult(..)`, `runStmt`, and `runStmtWithLocation`.  These
    were all deprecated and documented as slated for removal in GHC 7.14,
    which I figure means 8.2.
    
    See cf7573b8207bbb17c58612f3345e0b17d74cfb58 for an explanation of why
    this change was made.
    
    Reviewers: simonpj, hvr, austin, bgamari
    
    Reviewed By: bgamari
    
    Subscribers: thomie
    
    Differential Revision: https://phabricator.haskell.org/D2949
    
    GHC Trac Issues: #13095


>---------------------------------------------------------------

eee819943a0ea05af369fe3c728b865094e8fe33
 compiler/main/GHC.hs             |  5 -----
 compiler/main/InteractiveEval.hs | 41 +---------------------------------------
 2 files changed, 1 insertion(+), 45 deletions(-)

diff --git a/compiler/main/GHC.hs b/compiler/main/GHC.hs
index 59e42f9..031bd15 100644
--- a/compiler/main/GHC.hs
+++ b/compiler/main/GHC.hs
@@ -147,11 +147,6 @@ module GHC (
         InteractiveEval.back,
         InteractiveEval.forward,
 
-        -- ** Deprecated API
-        RunResult(..),
-        runStmt, runStmtWithLocation,
-        resume,
-
         -- * Abstract syntax elements
 
         -- ** Packages
diff --git a/compiler/main/InteractiveEval.hs b/compiler/main/InteractiveEval.hs
index 3cb1856..3c2973d 100644
--- a/compiler/main/InteractiveEval.hs
+++ b/compiler/main/InteractiveEval.hs
@@ -15,7 +15,6 @@ module InteractiveEval (
         runDecls, runDeclsWithLocation,
         isStmt, hasImport, isImport, isDecl,
         parseImportDecl, SingleStep(..),
-        resume,
         abandon, abandonAll,
         getResumeContext,
         getHistorySpan,
@@ -36,9 +35,7 @@ module InteractiveEval (
         parseExpr, compileParsedExpr,
         compileExpr, dynCompileExpr,
         compileExprRemote, compileParsedExprRemote,
-        Term(..), obtainTermFromId, obtainTermFromVal, reconstructType,
-        -- * Depcreated API (remove in GHC 7.14)
-        RunResult(..), runStmt, runStmtWithLocation,
+        Term(..), obtainTermFromId, obtainTermFromVal, reconstructType
         ) where
 
 #include "HsVersions.h"
@@ -97,7 +94,6 @@ import Control.Monad
 import GHC.Exts
 import Data.Array
 import Exception
-import Control.Concurrent
 
 -- -----------------------------------------------------------------------------
 -- running a statement interactively
@@ -195,38 +191,6 @@ execStmt stmt ExecOptions{..} = do
         handleRunStatus execSingleStep stmt bindings ids
                         status (emptyHistory size)
 
--- | The type returned by the deprecated 'runStmt' and
--- 'runStmtWithLocation' API
-data RunResult
-  = RunOk [Name]                -- ^ names bound by this evaluation
-  | RunException SomeException  -- ^ statement raised an exception
-  | RunBreak ThreadId [Name] (Maybe BreakInfo)
-
--- | Conver the old result type to the new result type
-execResultToRunResult :: ExecResult -> RunResult
-execResultToRunResult r =
-  case r of
-    ExecComplete{ execResult = Left ex } -> RunException ex
-    ExecComplete{ execResult = Right names } -> RunOk names
-    ExecBreak{..} -> RunBreak (error "no breakThreadId") breakNames breakInfo
-
--- Remove in GHC 7.14
-{-# DEPRECATED runStmt "use execStmt" #-}
--- | Run a statement in the current interactive context.  Statement
--- may bind multple values.
-runStmt :: GhcMonad m => String -> SingleStep -> m RunResult
-runStmt stmt step =
-  execResultToRunResult <$> execStmt stmt execOptions { execSingleStep = step }
-
--- Remove in GHC 7.14
-{-# DEPRECATED runStmtWithLocation "use execStmtWithLocation" #-}
-runStmtWithLocation :: GhcMonad m => String -> Int ->
-                       String -> SingleStep -> m RunResult
-runStmtWithLocation source linenumber expr step = do
-  execResultToRunResult <$>
-     execStmt expr execOptions { execSingleStep = step
-                               , execSourceFile = source
-                               , execLineNumber = linenumber }
 
 runDecls :: GhcMonad m => String -> m [Name]
 runDecls = runDeclsWithLocation "<interactive>" 1
@@ -375,9 +339,6 @@ handleRunStatus step expr bindings final_ids status history
     = panic "not_tracing" -- actually exhaustive, but GHC can't tell
 
 
-resume :: GhcMonad m => (SrcSpan->Bool) -> SingleStep -> m RunResult
-resume canLogSpan step = execResultToRunResult <$> resumeExec canLogSpan step
-
 resumeExec :: GhcMonad m => (SrcSpan->Bool) -> SingleStep -> m ExecResult
 resumeExec canLogSpan step
  = do



More information about the ghc-commits mailing list