{-# LANGUAGE CPP, MagicHash, RecordWildCards, BangPatterns #-}
{-# LANGUAGE LambdaCase #-}
{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-}
module GHC.Runtime.Eval (
Resume(..), History(..),
execStmt, execStmt', ExecOptions(..), execOptions, ExecResult(..), resumeExec,
runDecls, runDeclsWithLocation, runParsedDecls,
isStmt, hasImport, isImport, isDecl,
parseImportDecl, SingleStep(..),
abandon, abandonAll,
getResumeContext,
getHistorySpan,
getModBreaks,
getHistoryModule,
back, forward,
setContext, getContext,
availsToGlobalRdrEnv,
getNamesInScope,
getRdrNamesInScope,
moduleIsInterpreted,
getInfo,
exprType,
typeKind,
parseName,
parseInstanceHead,
getInstancesForType,
getDocs,
GetDocsFailure(..),
showModule,
moduleIsBootOrNotObjectLinkable,
parseExpr, compileParsedExpr,
compileExpr, dynCompileExpr,
compileExprRemote, compileParsedExprRemote,
Term(..), obtainTermFromId, obtainTermFromVal, reconstructType
) where
#include "HsVersions.h"
import GHC.Prelude
import GHC.Runtime.Eval.Types
import GHC.Runtime.Interpreter as GHCi
import GHC.Runtime.Interpreter.Types
import GHCi.Message
import GHCi.RemoteTypes
import GHC.Driver.Monad
import GHC.Driver.Main
import GHC.Hs
import GHC.Driver.Types
import GHC.Core.InstEnv
import GHC.Iface.Env ( newInteractiveBinder )
import GHC.Core.FamInstEnv ( FamInst )
import GHC.Core.FVs ( orphNamesOfFamInst )
import GHC.Core.TyCon
import GHC.Core.Type hiding( typeKind )
import qualified GHC.Core.Type as Type
import GHC.Types.RepType
import GHC.Tc.Utils.TcType
import GHC.Tc.Types.Constraint
import GHC.Tc.Types.Origin
import GHC.Core.Predicate
import GHC.Types.Var
import GHC.Types.Id as Id
import GHC.Types.Name hiding ( varName )
import GHC.Types.Name.Set
import GHC.Types.Avail
import GHC.Types.Name.Reader
import GHC.Types.Var.Env
import GHC.ByteCode.Types
import GHC.Runtime.Linker as Linker
import GHC.Driver.Session
import GHC.LanguageExtensions
import GHC.Types.Unique
import GHC.Types.Unique.Supply
import GHC.Utils.Monad
import GHC.Unit.Module
import GHC.Builtin.Names ( toDynName, pretendNameIsInScope )
import GHC.Builtin.Types ( isCTupleTyConName )
import GHC.Utils.Panic
import GHC.Data.Maybe
import GHC.Utils.Error
import GHC.Types.SrcLoc
import GHC.Runtime.Heap.Inspect
import GHC.Utils.Outputable
import GHC.Data.FastString
import GHC.Data.Bag
import GHC.Utils.Misc
import qualified GHC.Parser.Lexer as Lexer (P (..), ParseResult(..), unP, mkPStatePure)
import GHC.Parser.Lexer (ParserFlags)
import qualified GHC.Parser as Parser (parseStmt, parseModule, parseDeclaration, parseImport)
import System.Directory
import Data.Dynamic
import Data.Either
import qualified Data.IntMap as IntMap
import Data.List (find,intercalate)
import Data.Map (Map)
import qualified Data.Map as Map
import GHC.Data.StringBuffer (stringToStringBuffer)
import Control.Monad
import Control.Monad.Catch as MC
import Data.Array
import GHC.Utils.Exception
import Unsafe.Coerce ( unsafeCoerce )
import GHC.Tc.Module ( runTcInteractive, tcRnType, loadUnqualIfaces )
import GHC.Tc.Utils.Zonk ( ZonkFlexi (SkolemiseFlexi) )
import GHC.Tc.Utils.Env (tcGetInstEnvs)
import GHC.Tc.Utils.Instantiate (instDFunType)
import GHC.Tc.Solver (simplifyWantedsTcM)
import GHC.Tc.Utils.Monad
import GHC.Core.Class (classTyCon)
getResumeContext :: GhcMonad m => m [Resume]
getResumeContext :: forall (m :: * -> *). GhcMonad m => m [Resume]
getResumeContext = (HscEnv -> m [Resume]) -> m [Resume]
forall (m :: * -> *) a. GhcMonad m => (HscEnv -> m a) -> m a
withSession ([Resume] -> m [Resume]
forall (m :: * -> *) a. Monad m => a -> m a
return ([Resume] -> m [Resume])
-> (HscEnv -> [Resume]) -> HscEnv -> m [Resume]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. InteractiveContext -> [Resume]
ic_resume (InteractiveContext -> [Resume])
-> (HscEnv -> InteractiveContext) -> HscEnv -> [Resume]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HscEnv -> InteractiveContext
hsc_IC)
mkHistory :: HscEnv -> ForeignHValue -> BreakInfo -> History
mkHistory :: HscEnv -> ForeignHValue -> BreakInfo -> History
mkHistory HscEnv
hsc_env ForeignHValue
hval BreakInfo
bi = ForeignHValue -> BreakInfo -> [String] -> History
History ForeignHValue
hval BreakInfo
bi (HscEnv -> BreakInfo -> [String]
findEnclosingDecls HscEnv
hsc_env BreakInfo
bi)
getHistoryModule :: History -> Module
getHistoryModule :: History -> Module
getHistoryModule = BreakInfo -> Module
breakInfo_module (BreakInfo -> Module)
-> (History -> BreakInfo) -> History -> Module
forall b c a. (b -> c) -> (a -> b) -> a -> c
. History -> BreakInfo
historyBreakInfo
getHistorySpan :: HscEnv -> History -> SrcSpan
getHistorySpan :: HscEnv -> History -> SrcSpan
getHistorySpan HscEnv
hsc_env History{[String]
ForeignHValue
BreakInfo
historyEnclosingDecls :: History -> [String]
historyApStack :: History -> ForeignHValue
historyEnclosingDecls :: [String]
historyBreakInfo :: BreakInfo
historyApStack :: ForeignHValue
historyBreakInfo :: History -> BreakInfo
..} =
let BreakInfo{Int
Module
breakInfo_number :: BreakInfo -> Int
breakInfo_number :: Int
breakInfo_module :: Module
breakInfo_module :: BreakInfo -> Module
..} = BreakInfo
historyBreakInfo in
case HomePackageTable -> ModuleName -> Maybe HomeModInfo
lookupHpt (HscEnv -> HomePackageTable
hsc_HPT HscEnv
hsc_env) (Module -> ModuleName
forall unit. GenModule unit -> ModuleName
moduleName Module
breakInfo_module) of
Just HomeModInfo
hmi -> ModBreaks -> Array Int SrcSpan
modBreaks_locs (HomeModInfo -> ModBreaks
getModBreaks HomeModInfo
hmi) Array Int SrcSpan -> Int -> SrcSpan
forall i e. Ix i => Array i e -> i -> e
! Int
breakInfo_number
Maybe HomeModInfo
_ -> String -> SrcSpan
forall a. String -> a
panic String
"getHistorySpan"
findEnclosingDecls :: HscEnv -> BreakInfo -> [String]
findEnclosingDecls :: HscEnv -> BreakInfo -> [String]
findEnclosingDecls HscEnv
hsc_env (BreakInfo Module
modl Int
ix) =
let hmi :: HomeModInfo
hmi = String -> Maybe HomeModInfo -> HomeModInfo
forall a. HasCallStack => String -> Maybe a -> a
expectJust String
"findEnclosingDecls" (Maybe HomeModInfo -> HomeModInfo)
-> Maybe HomeModInfo -> HomeModInfo
forall a b. (a -> b) -> a -> b
$
HomePackageTable -> ModuleName -> Maybe HomeModInfo
lookupHpt (HscEnv -> HomePackageTable
hsc_HPT HscEnv
hsc_env) (Module -> ModuleName
forall unit. GenModule unit -> ModuleName
moduleName Module
modl)
mb :: ModBreaks
mb = HomeModInfo -> ModBreaks
getModBreaks HomeModInfo
hmi
in ModBreaks -> Array Int [String]
modBreaks_decls ModBreaks
mb Array Int [String] -> Int -> [String]
forall i e. Ix i => Array i e -> i -> e
! Int
ix
updateFixityEnv :: GhcMonad m => FixityEnv -> m ()
updateFixityEnv :: forall (m :: * -> *). GhcMonad m => FixityEnv -> m ()
updateFixityEnv FixityEnv
fix_env = do
HscEnv
hsc_env <- m HscEnv
forall (m :: * -> *). GhcMonad m => m HscEnv
getSession
let ic :: InteractiveContext
ic = HscEnv -> InteractiveContext
hsc_IC HscEnv
hsc_env
HscEnv -> m ()
forall (m :: * -> *). GhcMonad m => HscEnv -> m ()
setSession (HscEnv -> m ()) -> HscEnv -> m ()
forall a b. (a -> b) -> a -> b
$ HscEnv
hsc_env { hsc_IC :: InteractiveContext
hsc_IC = InteractiveContext
ic { ic_fix_env :: FixityEnv
ic_fix_env = FixityEnv
fix_env } }
execOptions :: ExecOptions
execOptions :: ExecOptions
execOptions = ExecOptions :: SingleStep
-> String
-> Int
-> (ForeignHValue -> EvalExpr ForeignHValue)
-> ExecOptions
ExecOptions
{ execSingleStep :: SingleStep
execSingleStep = SingleStep
RunToCompletion
, execSourceFile :: String
execSourceFile = String
"<interactive>"
, execLineNumber :: Int
execLineNumber = Int
1
, execWrap :: ForeignHValue -> EvalExpr ForeignHValue
execWrap = ForeignHValue -> EvalExpr ForeignHValue
forall a. a -> EvalExpr a
EvalThis
}
execStmt
:: GhcMonad m
=> String
-> ExecOptions
-> m ExecResult
execStmt :: forall (m :: * -> *).
GhcMonad m =>
String -> ExecOptions -> m ExecResult
execStmt String
input exec_opts :: ExecOptions
exec_opts@ExecOptions{Int
String
SingleStep
ForeignHValue -> EvalExpr ForeignHValue
execWrap :: ForeignHValue -> EvalExpr ForeignHValue
execLineNumber :: Int
execSourceFile :: String
execSingleStep :: SingleStep
execWrap :: ExecOptions -> ForeignHValue -> EvalExpr ForeignHValue
execLineNumber :: ExecOptions -> Int
execSourceFile :: ExecOptions -> String
execSingleStep :: ExecOptions -> SingleStep
..} = do
HscEnv
hsc_env <- m HscEnv
forall (m :: * -> *). GhcMonad m => m HscEnv
getSession
Maybe (GhciLStmt GhcPs)
mb_stmt <-
IO (Maybe (GhciLStmt GhcPs)) -> m (Maybe (GhciLStmt GhcPs))
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe (GhciLStmt GhcPs)) -> m (Maybe (GhciLStmt GhcPs)))
-> IO (Maybe (GhciLStmt GhcPs)) -> m (Maybe (GhciLStmt GhcPs))
forall a b. (a -> b) -> a -> b
$
HscEnv
-> Hsc (Maybe (GhciLStmt GhcPs)) -> IO (Maybe (GhciLStmt GhcPs))
forall a. HscEnv -> Hsc a -> IO a
runInteractiveHsc HscEnv
hsc_env (Hsc (Maybe (GhciLStmt GhcPs)) -> IO (Maybe (GhciLStmt GhcPs)))
-> Hsc (Maybe (GhciLStmt GhcPs)) -> IO (Maybe (GhciLStmt GhcPs))
forall a b. (a -> b) -> a -> b
$
String -> Int -> String -> Hsc (Maybe (GhciLStmt GhcPs))
hscParseStmtWithLocation String
execSourceFile Int
execLineNumber String
input
case Maybe (GhciLStmt GhcPs)
mb_stmt of
Maybe (GhciLStmt GhcPs)
Nothing -> ExecResult -> m ExecResult
forall (m :: * -> *) a. Monad m => a -> m a
return (Either SomeException [Name] -> Word64 -> ExecResult
ExecComplete ([Name] -> Either SomeException [Name]
forall a b. b -> Either a b
Right []) Word64
0)
Just GhciLStmt GhcPs
stmt -> GhciLStmt GhcPs -> String -> ExecOptions -> m ExecResult
forall (m :: * -> *).
GhcMonad m =>
GhciLStmt GhcPs -> String -> ExecOptions -> m ExecResult
execStmt' GhciLStmt GhcPs
stmt String
input ExecOptions
exec_opts
execStmt' :: GhcMonad m => GhciLStmt GhcPs -> String -> ExecOptions -> m ExecResult
execStmt' :: forall (m :: * -> *).
GhcMonad m =>
GhciLStmt GhcPs -> String -> ExecOptions -> m ExecResult
execStmt' GhciLStmt GhcPs
stmt String
stmt_text ExecOptions{Int
String
SingleStep
ForeignHValue -> EvalExpr ForeignHValue
execWrap :: ForeignHValue -> EvalExpr ForeignHValue
execLineNumber :: Int
execSourceFile :: String
execSingleStep :: SingleStep
execWrap :: ExecOptions -> ForeignHValue -> EvalExpr ForeignHValue
execLineNumber :: ExecOptions -> Int
execSourceFile :: ExecOptions -> String
execSingleStep :: ExecOptions -> SingleStep
..} = do
HscEnv
hsc_env <- m HscEnv
forall (m :: * -> *). GhcMonad m => m HscEnv
getSession
let ic :: InteractiveContext
ic = HscEnv -> InteractiveContext
hsc_IC HscEnv
hsc_env
idflags' :: DynFlags
idflags' = InteractiveContext -> DynFlags
ic_dflags InteractiveContext
ic DynFlags -> WarningFlag -> DynFlags
`wopt_unset` WarningFlag
Opt_WarnUnusedLocalBinds
hsc_env' :: HscEnv
hsc_env' = HscEnv -> HscEnv
mkInteractiveHscEnv (HscEnv
hsc_env{ hsc_IC :: InteractiveContext
hsc_IC = InteractiveContext
ic{ ic_dflags :: DynFlags
ic_dflags = DynFlags
idflags' } })
Maybe ([Id], ForeignHValue, FixityEnv)
r <- IO (Maybe ([Id], ForeignHValue, FixityEnv))
-> m (Maybe ([Id], ForeignHValue, FixityEnv))
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe ([Id], ForeignHValue, FixityEnv))
-> m (Maybe ([Id], ForeignHValue, FixityEnv)))
-> IO (Maybe ([Id], ForeignHValue, FixityEnv))
-> m (Maybe ([Id], ForeignHValue, FixityEnv))
forall a b. (a -> b) -> a -> b
$ HscEnv
-> GhciLStmt GhcPs -> IO (Maybe ([Id], ForeignHValue, FixityEnv))
hscParsedStmt HscEnv
hsc_env' GhciLStmt GhcPs
stmt
case Maybe ([Id], ForeignHValue, FixityEnv)
r of
Maybe ([Id], ForeignHValue, FixityEnv)
Nothing ->
ExecResult -> m ExecResult
forall (m :: * -> *) a. Monad m => a -> m a
return (Either SomeException [Name] -> Word64 -> ExecResult
ExecComplete ([Name] -> Either SomeException [Name]
forall a b. b -> Either a b
Right []) Word64
0)
Just ([Id]
ids, ForeignHValue
hval, FixityEnv
fix_env) -> do
FixityEnv -> m ()
forall (m :: * -> *). GhcMonad m => FixityEnv -> m ()
updateFixityEnv FixityEnv
fix_env
EvalStatus_ [ForeignHValue] [HValueRef]
status <-
m (EvalStatus_ [ForeignHValue] [HValueRef])
-> m (EvalStatus_ [ForeignHValue] [HValueRef])
forall (m :: * -> *) a. GhcMonad m => m a -> m a
withVirtualCWD (m (EvalStatus_ [ForeignHValue] [HValueRef])
-> m (EvalStatus_ [ForeignHValue] [HValueRef]))
-> m (EvalStatus_ [ForeignHValue] [HValueRef])
-> m (EvalStatus_ [ForeignHValue] [HValueRef])
forall a b. (a -> b) -> a -> b
$
IO (EvalStatus_ [ForeignHValue] [HValueRef])
-> m (EvalStatus_ [ForeignHValue] [HValueRef])
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (EvalStatus_ [ForeignHValue] [HValueRef])
-> m (EvalStatus_ [ForeignHValue] [HValueRef]))
-> IO (EvalStatus_ [ForeignHValue] [HValueRef])
-> m (EvalStatus_ [ForeignHValue] [HValueRef])
forall a b. (a -> b) -> a -> b
$
HscEnv
-> Bool
-> EvalExpr ForeignHValue
-> IO (EvalStatus_ [ForeignHValue] [HValueRef])
evalStmt HscEnv
hsc_env' (SingleStep -> Bool
isStep SingleStep
execSingleStep) (ForeignHValue -> EvalExpr ForeignHValue
execWrap ForeignHValue
hval)
let ic :: InteractiveContext
ic = HscEnv -> InteractiveContext
hsc_IC HscEnv
hsc_env
bindings :: ([TyThing], GlobalRdrEnv)
bindings = (InteractiveContext -> [TyThing]
ic_tythings InteractiveContext
ic, InteractiveContext -> GlobalRdrEnv
ic_rn_gbl_env InteractiveContext
ic)
size :: Int
size = DynFlags -> Int
ghciHistSize DynFlags
idflags'
SingleStep
-> String
-> ([TyThing], GlobalRdrEnv)
-> [Id]
-> EvalStatus_ [ForeignHValue] [HValueRef]
-> BoundedList History
-> m ExecResult
forall (m :: * -> *).
GhcMonad m =>
SingleStep
-> String
-> ([TyThing], GlobalRdrEnv)
-> [Id]
-> EvalStatus_ [ForeignHValue] [HValueRef]
-> BoundedList History
-> m ExecResult
handleRunStatus SingleStep
execSingleStep String
stmt_text ([TyThing], GlobalRdrEnv)
bindings [Id]
ids
EvalStatus_ [ForeignHValue] [HValueRef]
status (Int -> BoundedList History
emptyHistory Int
size)
runDecls :: GhcMonad m => String -> m [Name]
runDecls :: forall (m :: * -> *). GhcMonad m => String -> m [Name]
runDecls = String -> Int -> String -> m [Name]
forall (m :: * -> *).
GhcMonad m =>
String -> Int -> String -> m [Name]
runDeclsWithLocation String
"<interactive>" Int
1
runDeclsWithLocation :: GhcMonad m => String -> Int -> String -> m [Name]
runDeclsWithLocation :: forall (m :: * -> *).
GhcMonad m =>
String -> Int -> String -> m [Name]
runDeclsWithLocation String
source Int
line_num String
input = do
HscEnv
hsc_env <- m HscEnv
forall (m :: * -> *). GhcMonad m => m HscEnv
getSession
[LHsDecl GhcPs]
decls <- IO [LHsDecl GhcPs] -> m [LHsDecl GhcPs]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (HscEnv -> String -> Int -> String -> IO [LHsDecl GhcPs]
hscParseDeclsWithLocation HscEnv
hsc_env String
source Int
line_num String
input)
[LHsDecl GhcPs] -> m [Name]
forall (m :: * -> *). GhcMonad m => [LHsDecl GhcPs] -> m [Name]
runParsedDecls [LHsDecl GhcPs]
decls
runParsedDecls :: GhcMonad m => [LHsDecl GhcPs] -> m [Name]
runParsedDecls :: forall (m :: * -> *). GhcMonad m => [LHsDecl GhcPs] -> m [Name]
runParsedDecls [LHsDecl GhcPs]
decls = do
HscEnv
hsc_env <- m HscEnv
forall (m :: * -> *). GhcMonad m => m HscEnv
getSession
([TyThing]
tyThings, InteractiveContext
ic) <- IO ([TyThing], InteractiveContext)
-> m ([TyThing], InteractiveContext)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (HscEnv -> [LHsDecl GhcPs] -> IO ([TyThing], InteractiveContext)
hscParsedDecls HscEnv
hsc_env [LHsDecl GhcPs]
decls)
HscEnv -> m ()
forall (m :: * -> *). GhcMonad m => HscEnv -> m ()
setSession (HscEnv -> m ()) -> HscEnv -> m ()
forall a b. (a -> b) -> a -> b
$ HscEnv
hsc_env { hsc_IC :: InteractiveContext
hsc_IC = InteractiveContext
ic }
HscEnv
hsc_env <- m HscEnv
forall (m :: * -> *). GhcMonad m => m HscEnv
getSession
HscEnv
hsc_env' <- IO HscEnv -> m HscEnv
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO HscEnv -> m HscEnv) -> IO HscEnv -> m HscEnv
forall a b. (a -> b) -> a -> b
$ HscEnv -> IO HscEnv
rttiEnvironment HscEnv
hsc_env
HscEnv -> m ()
forall (m :: * -> *). GhcMonad m => HscEnv -> m ()
setSession HscEnv
hsc_env'
[Name] -> m [Name]
forall (m :: * -> *) a. Monad m => a -> m a
return ([Name] -> m [Name]) -> [Name] -> m [Name]
forall a b. (a -> b) -> a -> b
$ (Name -> Bool) -> [Name] -> [Name]
forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not (Bool -> Bool) -> (Name -> Bool) -> Name -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. OccName -> Bool
isDerivedOccName (OccName -> Bool) -> (Name -> OccName) -> Name -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Name -> OccName
nameOccName)
([Name] -> [Name]) -> [Name] -> [Name]
forall a b. (a -> b) -> a -> b
$ (TyThing -> Name) -> [TyThing] -> [Name]
forall a b. (a -> b) -> [a] -> [b]
map TyThing -> Name
forall a. NamedThing a => a -> Name
getName [TyThing]
tyThings
withVirtualCWD :: GhcMonad m => m a -> m a
withVirtualCWD :: forall (m :: * -> *) a. GhcMonad m => m a -> m a
withVirtualCWD m a
m = do
HscEnv
hsc_env <- m HscEnv
forall (m :: * -> *). GhcMonad m => m HscEnv
getSession
case HscEnv -> Maybe Interp
hsc_interp HscEnv
hsc_env of
Just (ExternalInterp {}) -> m a
m
Maybe Interp
_ -> do
let ic :: InteractiveContext
ic = HscEnv -> InteractiveContext
hsc_IC HscEnv
hsc_env
let set_cwd :: m String
set_cwd = do
String
dir <- IO String -> m String
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO String -> m String) -> IO String -> m String
forall a b. (a -> b) -> a -> b
$ IO String
getCurrentDirectory
case InteractiveContext -> Maybe String
ic_cwd InteractiveContext
ic of
Just String
dir -> IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ String -> IO ()
setCurrentDirectory String
dir
Maybe String
Nothing -> () -> m ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
String -> m String
forall (m :: * -> *) a. Monad m => a -> m a
return String
dir
reset_cwd :: String -> m ()
reset_cwd String
orig_dir = do
String
virt_dir <- IO String -> m String
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO String -> m String) -> IO String -> m String
forall a b. (a -> b) -> a -> b
$ IO String
getCurrentDirectory
HscEnv
hsc_env <- m HscEnv
forall (m :: * -> *). GhcMonad m => m HscEnv
getSession
let old_IC :: InteractiveContext
old_IC = HscEnv -> InteractiveContext
hsc_IC HscEnv
hsc_env
HscEnv -> m ()
forall (m :: * -> *). GhcMonad m => HscEnv -> m ()
setSession HscEnv
hsc_env{ hsc_IC :: InteractiveContext
hsc_IC = InteractiveContext
old_IC{ ic_cwd :: Maybe String
ic_cwd = String -> Maybe String
forall a. a -> Maybe a
Just String
virt_dir } }
IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ String -> IO ()
setCurrentDirectory String
orig_dir
m String -> (String -> m ()) -> (String -> m a) -> m a
forall (m :: * -> *) a c b.
MonadMask m =>
m a -> (a -> m c) -> (a -> m b) -> m b
MC.bracket m String
set_cwd String -> m ()
forall {m :: * -> *}. GhcMonad m => String -> m ()
reset_cwd ((String -> m a) -> m a) -> (String -> m a) -> m a
forall a b. (a -> b) -> a -> b
$ \String
_ -> m a
m
parseImportDecl :: GhcMonad m => String -> m (ImportDecl GhcPs)
parseImportDecl :: forall (m :: * -> *). GhcMonad m => String -> m (ImportDecl GhcPs)
parseImportDecl String
expr = (HscEnv -> m (ImportDecl GhcPs)) -> m (ImportDecl GhcPs)
forall (m :: * -> *) a. GhcMonad m => (HscEnv -> m a) -> m a
withSession ((HscEnv -> m (ImportDecl GhcPs)) -> m (ImportDecl GhcPs))
-> (HscEnv -> m (ImportDecl GhcPs)) -> m (ImportDecl GhcPs)
forall a b. (a -> b) -> a -> b
$ \HscEnv
hsc_env -> IO (ImportDecl GhcPs) -> m (ImportDecl GhcPs)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (ImportDecl GhcPs) -> m (ImportDecl GhcPs))
-> IO (ImportDecl GhcPs) -> m (ImportDecl GhcPs)
forall a b. (a -> b) -> a -> b
$ HscEnv -> String -> IO (ImportDecl GhcPs)
hscImport HscEnv
hsc_env String
expr
emptyHistory :: Int -> BoundedList History
emptyHistory :: Int -> BoundedList History
emptyHistory Int
size = Int -> BoundedList History
forall a. Int -> BoundedList a
nilBL Int
size
handleRunStatus :: GhcMonad m
=> SingleStep -> String-> ([TyThing],GlobalRdrEnv) -> [Id]
-> EvalStatus_ [ForeignHValue] [HValueRef]
-> BoundedList History
-> m ExecResult
handleRunStatus :: forall (m :: * -> *).
GhcMonad m =>
SingleStep
-> String
-> ([TyThing], GlobalRdrEnv)
-> [Id]
-> EvalStatus_ [ForeignHValue] [HValueRef]
-> BoundedList History
-> m ExecResult
handleRunStatus SingleStep
step String
expr ([TyThing], GlobalRdrEnv)
bindings [Id]
final_ids EvalStatus_ [ForeignHValue] [HValueRef]
status BoundedList History
history
| SingleStep
RunAndLogSteps <- SingleStep
step = m ExecResult
tracing
| Bool
otherwise = m ExecResult
not_tracing
where
tracing :: m ExecResult
tracing
| EvalBreak Bool
is_exception HValueRef
apStack_ref Int
ix Int
mod_uniq RemoteRef (ResumeContext [HValueRef])
resume_ctxt RemotePtr CostCentreStack
_ccs <- EvalStatus_ [ForeignHValue] [HValueRef]
status
, Bool -> Bool
not Bool
is_exception
= do
HscEnv
hsc_env <- m HscEnv
forall (m :: * -> *). GhcMonad m => m HscEnv
getSession
let hmi :: HomeModInfo
hmi = String -> Maybe HomeModInfo -> HomeModInfo
forall a. HasCallStack => String -> Maybe a -> a
expectJust String
"handleRunStatus" (Maybe HomeModInfo -> HomeModInfo)
-> Maybe HomeModInfo -> HomeModInfo
forall a b. (a -> b) -> a -> b
$
HomePackageTable -> Unique -> Maybe HomeModInfo
lookupHptDirectly (HscEnv -> HomePackageTable
hsc_HPT HscEnv
hsc_env)
(Int -> Unique
mkUniqueGrimily Int
mod_uniq)
modl :: Module
modl = ModIface_ 'ModIfaceFinal -> Module
forall (phase :: ModIfacePhase). ModIface_ phase -> Module
mi_module (HomeModInfo -> ModIface_ 'ModIfaceFinal
hm_iface HomeModInfo
hmi)
breaks :: ModBreaks
breaks = HomeModInfo -> ModBreaks
getModBreaks HomeModInfo
hmi
Bool
b <- IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$
HscEnv -> ForeignRef BreakArray -> Int -> IO Bool
breakpointStatus HscEnv
hsc_env (ModBreaks -> ForeignRef BreakArray
modBreaks_flags ModBreaks
breaks) Int
ix
if Bool
b
then m ExecResult
not_tracing
else do
ForeignHValue
apStack_fhv <- IO ForeignHValue -> m ForeignHValue
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ForeignHValue -> m ForeignHValue)
-> IO ForeignHValue -> m ForeignHValue
forall a b. (a -> b) -> a -> b
$ HscEnv -> HValueRef -> IO ForeignHValue
forall a. HscEnv -> RemoteRef a -> IO (ForeignRef a)
mkFinalizedHValue HscEnv
hsc_env HValueRef
apStack_ref
let bi :: BreakInfo
bi = Module -> Int -> BreakInfo
BreakInfo Module
modl Int
ix
!history' :: BoundedList History
history' = HscEnv -> ForeignHValue -> BreakInfo -> History
mkHistory HscEnv
hsc_env ForeignHValue
apStack_fhv BreakInfo
bi History -> BoundedList History -> BoundedList History
forall a. a -> BoundedList a -> BoundedList a
`consBL` BoundedList History
history
ForeignRef (ResumeContext [HValueRef])
fhv <- IO (ForeignRef (ResumeContext [HValueRef]))
-> m (ForeignRef (ResumeContext [HValueRef]))
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (ForeignRef (ResumeContext [HValueRef]))
-> m (ForeignRef (ResumeContext [HValueRef])))
-> IO (ForeignRef (ResumeContext [HValueRef]))
-> m (ForeignRef (ResumeContext [HValueRef]))
forall a b. (a -> b) -> a -> b
$ HscEnv
-> RemoteRef (ResumeContext [HValueRef])
-> IO (ForeignRef (ResumeContext [HValueRef]))
forall a. HscEnv -> RemoteRef a -> IO (ForeignRef a)
mkFinalizedHValue HscEnv
hsc_env RemoteRef (ResumeContext [HValueRef])
resume_ctxt
EvalStatus_ [ForeignHValue] [HValueRef]
status <- IO (EvalStatus_ [ForeignHValue] [HValueRef])
-> m (EvalStatus_ [ForeignHValue] [HValueRef])
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (EvalStatus_ [ForeignHValue] [HValueRef])
-> m (EvalStatus_ [ForeignHValue] [HValueRef]))
-> IO (EvalStatus_ [ForeignHValue] [HValueRef])
-> m (EvalStatus_ [ForeignHValue] [HValueRef])
forall a b. (a -> b) -> a -> b
$ HscEnv
-> Bool
-> ForeignRef (ResumeContext [HValueRef])
-> IO (EvalStatus_ [ForeignHValue] [HValueRef])
GHCi.resumeStmt HscEnv
hsc_env Bool
True ForeignRef (ResumeContext [HValueRef])
fhv
SingleStep
-> String
-> ([TyThing], GlobalRdrEnv)
-> [Id]
-> EvalStatus_ [ForeignHValue] [HValueRef]
-> BoundedList History
-> m ExecResult
forall (m :: * -> *).
GhcMonad m =>
SingleStep
-> String
-> ([TyThing], GlobalRdrEnv)
-> [Id]
-> EvalStatus_ [ForeignHValue] [HValueRef]
-> BoundedList History
-> m ExecResult
handleRunStatus SingleStep
RunAndLogSteps String
expr ([TyThing], GlobalRdrEnv)
bindings [Id]
final_ids
EvalStatus_ [ForeignHValue] [HValueRef]
status BoundedList History
history'
| Bool
otherwise
= m ExecResult
not_tracing
not_tracing :: m ExecResult
not_tracing
| EvalBreak Bool
is_exception HValueRef
apStack_ref Int
ix Int
mod_uniq RemoteRef (ResumeContext [HValueRef])
resume_ctxt RemotePtr CostCentreStack
ccs <- EvalStatus_ [ForeignHValue] [HValueRef]
status
= do
HscEnv
hsc_env <- m HscEnv
forall (m :: * -> *). GhcMonad m => m HscEnv
getSession
ForeignRef (ResumeContext [HValueRef])
resume_ctxt_fhv <- IO (ForeignRef (ResumeContext [HValueRef]))
-> m (ForeignRef (ResumeContext [HValueRef]))
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (ForeignRef (ResumeContext [HValueRef]))
-> m (ForeignRef (ResumeContext [HValueRef])))
-> IO (ForeignRef (ResumeContext [HValueRef]))
-> m (ForeignRef (ResumeContext [HValueRef]))
forall a b. (a -> b) -> a -> b
$ HscEnv
-> RemoteRef (ResumeContext [HValueRef])
-> IO (ForeignRef (ResumeContext [HValueRef]))
forall a. HscEnv -> RemoteRef a -> IO (ForeignRef a)
mkFinalizedHValue HscEnv
hsc_env RemoteRef (ResumeContext [HValueRef])
resume_ctxt
ForeignHValue
apStack_fhv <- IO ForeignHValue -> m ForeignHValue
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ForeignHValue -> m ForeignHValue)
-> IO ForeignHValue -> m ForeignHValue
forall a b. (a -> b) -> a -> b
$ HscEnv -> HValueRef -> IO ForeignHValue
forall a. HscEnv -> RemoteRef a -> IO (ForeignRef a)
mkFinalizedHValue HscEnv
hsc_env HValueRef
apStack_ref
let hmi :: HomeModInfo
hmi = String -> Maybe HomeModInfo -> HomeModInfo
forall a. HasCallStack => String -> Maybe a -> a
expectJust String
"handleRunStatus" (Maybe HomeModInfo -> HomeModInfo)
-> Maybe HomeModInfo -> HomeModInfo
forall a b. (a -> b) -> a -> b
$
HomePackageTable -> Unique -> Maybe HomeModInfo
lookupHptDirectly (HscEnv -> HomePackageTable
hsc_HPT HscEnv
hsc_env)
(Int -> Unique
mkUniqueGrimily Int
mod_uniq)
modl :: Module
modl = ModIface_ 'ModIfaceFinal -> Module
forall (phase :: ModIfacePhase). ModIface_ phase -> Module
mi_module (HomeModInfo -> ModIface_ 'ModIfaceFinal
hm_iface HomeModInfo
hmi)
bp :: Maybe BreakInfo
bp | Bool
is_exception = Maybe BreakInfo
forall a. Maybe a
Nothing
| Bool
otherwise = BreakInfo -> Maybe BreakInfo
forall a. a -> Maybe a
Just (Module -> Int -> BreakInfo
BreakInfo Module
modl Int
ix)
(HscEnv
hsc_env1, [Name]
names, SrcSpan
span, String
decl) <- IO (HscEnv, [Name], SrcSpan, String)
-> m (HscEnv, [Name], SrcSpan, String)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (HscEnv, [Name], SrcSpan, String)
-> m (HscEnv, [Name], SrcSpan, String))
-> IO (HscEnv, [Name], SrcSpan, String)
-> m (HscEnv, [Name], SrcSpan, String)
forall a b. (a -> b) -> a -> b
$
HscEnv
-> ForeignHValue
-> Maybe BreakInfo
-> IO (HscEnv, [Name], SrcSpan, String)
bindLocalsAtBreakpoint HscEnv
hsc_env ForeignHValue
apStack_fhv Maybe BreakInfo
bp
let
resume :: Resume
resume = Resume :: String
-> ForeignRef (ResumeContext [HValueRef])
-> ([TyThing], GlobalRdrEnv)
-> [Id]
-> ForeignHValue
-> Maybe BreakInfo
-> SrcSpan
-> String
-> RemotePtr CostCentreStack
-> [History]
-> Int
-> Resume
Resume
{ resumeStmt :: String
resumeStmt = String
expr, resumeContext :: ForeignRef (ResumeContext [HValueRef])
resumeContext = ForeignRef (ResumeContext [HValueRef])
resume_ctxt_fhv
, resumeBindings :: ([TyThing], GlobalRdrEnv)
resumeBindings = ([TyThing], GlobalRdrEnv)
bindings, resumeFinalIds :: [Id]
resumeFinalIds = [Id]
final_ids
, resumeApStack :: ForeignHValue
resumeApStack = ForeignHValue
apStack_fhv
, resumeBreakInfo :: Maybe BreakInfo
resumeBreakInfo = Maybe BreakInfo
bp
, resumeSpan :: SrcSpan
resumeSpan = SrcSpan
span, resumeHistory :: [History]
resumeHistory = BoundedList History -> [History]
forall a. BoundedList a -> [a]
toListBL BoundedList History
history
, resumeDecl :: String
resumeDecl = String
decl
, resumeCCS :: RemotePtr CostCentreStack
resumeCCS = RemotePtr CostCentreStack
ccs
, resumeHistoryIx :: Int
resumeHistoryIx = Int
0 }
hsc_env2 :: HscEnv
hsc_env2 = HscEnv -> Resume -> HscEnv
pushResume HscEnv
hsc_env1 Resume
resume
HscEnv -> m ()
forall (m :: * -> *). GhcMonad m => HscEnv -> m ()
setSession HscEnv
hsc_env2
ExecResult -> m ExecResult
forall (m :: * -> *) a. Monad m => a -> m a
return ([Name] -> Maybe BreakInfo -> ExecResult
ExecBreak [Name]
names Maybe BreakInfo
bp)
| EvalComplete Word64
allocs (EvalSuccess [ForeignHValue]
hvals) <- EvalStatus_ [ForeignHValue] [HValueRef]
status
= do HscEnv
hsc_env <- m HscEnv
forall (m :: * -> *). GhcMonad m => m HscEnv
getSession
let final_ic :: InteractiveContext
final_ic = InteractiveContext -> [Id] -> InteractiveContext
extendInteractiveContextWithIds (HscEnv -> InteractiveContext
hsc_IC HscEnv
hsc_env) [Id]
final_ids
final_names :: [Name]
final_names = (Id -> Name) -> [Id] -> [Name]
forall a b. (a -> b) -> [a] -> [b]
map Id -> Name
forall a. NamedThing a => a -> Name
getName [Id]
final_ids
dl :: DynLinker
dl = HscEnv -> DynLinker
hsc_dynLinker HscEnv
hsc_env
IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ DynLinker -> [(Name, ForeignHValue)] -> IO ()
Linker.extendLinkEnv DynLinker
dl ([Name] -> [ForeignHValue] -> [(Name, ForeignHValue)]
forall a b. [a] -> [b] -> [(a, b)]
zip [Name]
final_names [ForeignHValue]
hvals)
HscEnv
hsc_env' <- IO HscEnv -> m HscEnv
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO HscEnv -> m HscEnv) -> IO HscEnv -> m HscEnv
forall a b. (a -> b) -> a -> b
$ HscEnv -> IO HscEnv
rttiEnvironment HscEnv
hsc_env{hsc_IC :: InteractiveContext
hsc_IC=InteractiveContext
final_ic}
HscEnv -> m ()
forall (m :: * -> *). GhcMonad m => HscEnv -> m ()
setSession HscEnv
hsc_env'
ExecResult -> m ExecResult
forall (m :: * -> *) a. Monad m => a -> m a
return (Either SomeException [Name] -> Word64 -> ExecResult
ExecComplete ([Name] -> Either SomeException [Name]
forall a b. b -> Either a b
Right [Name]
final_names) Word64
allocs)
| EvalComplete Word64
alloc (EvalException SerializableException
e) <- EvalStatus_ [ForeignHValue] [HValueRef]
status
= ExecResult -> m ExecResult
forall (m :: * -> *) a. Monad m => a -> m a
return (Either SomeException [Name] -> Word64 -> ExecResult
ExecComplete (SomeException -> Either SomeException [Name]
forall a b. a -> Either a b
Left (SerializableException -> SomeException
fromSerializableException SerializableException
e)) Word64
alloc)
#if __GLASGOW_HASKELL__ <= 810
| otherwise
= panic "not_tracing"
#endif
resumeExec :: GhcMonad m => (SrcSpan->Bool) -> SingleStep -> m ExecResult
resumeExec :: forall (m :: * -> *).
GhcMonad m =>
(SrcSpan -> Bool) -> SingleStep -> m ExecResult
resumeExec SrcSpan -> Bool
canLogSpan SingleStep
step
= do
HscEnv
hsc_env <- m HscEnv
forall (m :: * -> *). GhcMonad m => m HscEnv
getSession
let ic :: InteractiveContext
ic = HscEnv -> InteractiveContext
hsc_IC HscEnv
hsc_env
resume :: [Resume]
resume = InteractiveContext -> [Resume]
ic_resume InteractiveContext
ic
case [Resume]
resume of
[] -> IO ExecResult -> m ExecResult
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ExecResult -> m ExecResult) -> IO ExecResult -> m ExecResult
forall a b. (a -> b) -> a -> b
$
GhcException -> IO ExecResult
forall a. GhcException -> IO a
throwGhcExceptionIO (String -> GhcException
ProgramError String
"not stopped at a breakpoint")
(Resume
r:[Resume]
rs) -> do
let ([TyThing]
resume_tmp_te,GlobalRdrEnv
resume_rdr_env) = Resume -> ([TyThing], GlobalRdrEnv)
resumeBindings Resume
r
ic' :: InteractiveContext
ic' = InteractiveContext
ic { ic_tythings :: [TyThing]
ic_tythings = [TyThing]
resume_tmp_te,
ic_rn_gbl_env :: GlobalRdrEnv
ic_rn_gbl_env = GlobalRdrEnv
resume_rdr_env,
ic_resume :: [Resume]
ic_resume = [Resume]
rs }
HscEnv -> m ()
forall (m :: * -> *). GhcMonad m => HscEnv -> m ()
setSession HscEnv
hsc_env{ hsc_IC :: InteractiveContext
hsc_IC = InteractiveContext
ic' }
let old_names :: [Name]
old_names = (TyThing -> Name) -> [TyThing] -> [Name]
forall a b. (a -> b) -> [a] -> [b]
map TyThing -> Name
forall a. NamedThing a => a -> Name
getName [TyThing]
resume_tmp_te
new_names :: [Name]
new_names = [ Name
n | TyThing
thing <- InteractiveContext -> [TyThing]
ic_tythings InteractiveContext
ic
, let n :: Name
n = TyThing -> Name
forall a. NamedThing a => a -> Name
getName TyThing
thing
, Bool -> Bool
not (Name
n Name -> [Name] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Name]
old_names) ]
dl :: DynLinker
dl = HscEnv -> DynLinker
hsc_dynLinker HscEnv
hsc_env
IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ DynLinker -> [Name] -> IO ()
Linker.deleteFromLinkEnv DynLinker
dl [Name]
new_names
case Resume
r of
Resume { resumeStmt :: Resume -> String
resumeStmt = String
expr, resumeContext :: Resume -> ForeignRef (ResumeContext [HValueRef])
resumeContext = ForeignRef (ResumeContext [HValueRef])
fhv
, resumeBindings :: Resume -> ([TyThing], GlobalRdrEnv)
resumeBindings = ([TyThing], GlobalRdrEnv)
bindings, resumeFinalIds :: Resume -> [Id]
resumeFinalIds = [Id]
final_ids
, resumeApStack :: Resume -> ForeignHValue
resumeApStack = ForeignHValue
apStack, resumeBreakInfo :: Resume -> Maybe BreakInfo
resumeBreakInfo = Maybe BreakInfo
mb_brkpt
, resumeSpan :: Resume -> SrcSpan
resumeSpan = SrcSpan
span
, resumeHistory :: Resume -> [History]
resumeHistory = [History]
hist } -> do
m ExecResult -> m ExecResult
forall (m :: * -> *) a. GhcMonad m => m a -> m a
withVirtualCWD (m ExecResult -> m ExecResult) -> m ExecResult -> m ExecResult
forall a b. (a -> b) -> a -> b
$ do
EvalStatus_ [ForeignHValue] [HValueRef]
status <- IO (EvalStatus_ [ForeignHValue] [HValueRef])
-> m (EvalStatus_ [ForeignHValue] [HValueRef])
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (EvalStatus_ [ForeignHValue] [HValueRef])
-> m (EvalStatus_ [ForeignHValue] [HValueRef]))
-> IO (EvalStatus_ [ForeignHValue] [HValueRef])
-> m (EvalStatus_ [ForeignHValue] [HValueRef])
forall a b. (a -> b) -> a -> b
$ HscEnv
-> Bool
-> ForeignRef (ResumeContext [HValueRef])
-> IO (EvalStatus_ [ForeignHValue] [HValueRef])
GHCi.resumeStmt HscEnv
hsc_env (SingleStep -> Bool
isStep SingleStep
step) ForeignRef (ResumeContext [HValueRef])
fhv
let prevHistoryLst :: BoundedList History
prevHistoryLst = Int -> [History] -> BoundedList History
forall a. Int -> [a] -> BoundedList a
fromListBL Int
50 [History]
hist
hist' :: BoundedList History
hist' = case Maybe BreakInfo
mb_brkpt of
Maybe BreakInfo
Nothing -> BoundedList History
prevHistoryLst
Just BreakInfo
bi
| Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$SrcSpan -> Bool
canLogSpan SrcSpan
span -> BoundedList History
prevHistoryLst
| Bool
otherwise -> HscEnv -> ForeignHValue -> BreakInfo -> History
mkHistory HscEnv
hsc_env ForeignHValue
apStack BreakInfo
bi History -> BoundedList History -> BoundedList History
forall a. a -> BoundedList a -> BoundedList a
`consBL`
Int -> [History] -> BoundedList History
forall a. Int -> [a] -> BoundedList a
fromListBL Int
50 [History]
hist
SingleStep
-> String
-> ([TyThing], GlobalRdrEnv)
-> [Id]
-> EvalStatus_ [ForeignHValue] [HValueRef]
-> BoundedList History
-> m ExecResult
forall (m :: * -> *).
GhcMonad m =>
SingleStep
-> String
-> ([TyThing], GlobalRdrEnv)
-> [Id]
-> EvalStatus_ [ForeignHValue] [HValueRef]
-> BoundedList History
-> m ExecResult
handleRunStatus SingleStep
step String
expr ([TyThing], GlobalRdrEnv)
bindings [Id]
final_ids EvalStatus_ [ForeignHValue] [HValueRef]
status BoundedList History
hist'
back :: GhcMonad m => Int -> m ([Name], Int, SrcSpan, String)
back :: forall (m :: * -> *).
GhcMonad m =>
Int -> m ([Name], Int, SrcSpan, String)
back Int
n = (Int -> Int) -> m ([Name], Int, SrcSpan, String)
forall (m :: * -> *).
GhcMonad m =>
(Int -> Int) -> m ([Name], Int, SrcSpan, String)
moveHist (Int -> Int -> Int
forall a. Num a => a -> a -> a
+Int
n)
forward :: GhcMonad m => Int -> m ([Name], Int, SrcSpan, String)
forward :: forall (m :: * -> *).
GhcMonad m =>
Int -> m ([Name], Int, SrcSpan, String)
forward Int
n = (Int -> Int) -> m ([Name], Int, SrcSpan, String)
forall (m :: * -> *).
GhcMonad m =>
(Int -> Int) -> m ([Name], Int, SrcSpan, String)
moveHist (Int -> Int -> Int
forall a. Num a => a -> a -> a
subtract Int
n)
moveHist :: GhcMonad m => (Int -> Int) -> m ([Name], Int, SrcSpan, String)
moveHist :: forall (m :: * -> *).
GhcMonad m =>
(Int -> Int) -> m ([Name], Int, SrcSpan, String)
moveHist Int -> Int
fn = do
HscEnv
hsc_env <- m HscEnv
forall (m :: * -> *). GhcMonad m => m HscEnv
getSession
case InteractiveContext -> [Resume]
ic_resume (HscEnv -> InteractiveContext
hsc_IC HscEnv
hsc_env) of
[] -> IO ([Name], Int, SrcSpan, String)
-> m ([Name], Int, SrcSpan, String)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ([Name], Int, SrcSpan, String)
-> m ([Name], Int, SrcSpan, String))
-> IO ([Name], Int, SrcSpan, String)
-> m ([Name], Int, SrcSpan, String)
forall a b. (a -> b) -> a -> b
$
GhcException -> IO ([Name], Int, SrcSpan, String)
forall a. GhcException -> IO a
throwGhcExceptionIO (String -> GhcException
ProgramError String
"not stopped at a breakpoint")
(Resume
r:[Resume]
rs) -> do
let ix :: Int
ix = Resume -> Int
resumeHistoryIx Resume
r
history :: [History]
history = Resume -> [History]
resumeHistory Resume
r
new_ix :: Int
new_ix = Int -> Int
fn Int
ix
Bool -> m () -> m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when ([History]
history [History] -> Int -> Bool
forall a. [a] -> Int -> Bool
`lengthLessThan` Int
new_ix) (m () -> m ()) -> m () -> m ()
forall a b. (a -> b) -> a -> b
$ IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$
GhcException -> IO ()
forall a. GhcException -> IO a
throwGhcExceptionIO (String -> GhcException
ProgramError String
"no more logged breakpoints")
Bool -> m () -> m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Int
new_ix Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
0) (m () -> m ()) -> m () -> m ()
forall a b. (a -> b) -> a -> b
$ IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$
GhcException -> IO ()
forall a. GhcException -> IO a
throwGhcExceptionIO (String -> GhcException
ProgramError String
"already at the beginning of the history")
let
update_ic :: ForeignHValue
-> Maybe BreakInfo -> m ([Name], Int, SrcSpan, String)
update_ic ForeignHValue
apStack Maybe BreakInfo
mb_info = do
(HscEnv
hsc_env1, [Name]
names, SrcSpan
span, String
decl) <-
IO (HscEnv, [Name], SrcSpan, String)
-> m (HscEnv, [Name], SrcSpan, String)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (HscEnv, [Name], SrcSpan, String)
-> m (HscEnv, [Name], SrcSpan, String))
-> IO (HscEnv, [Name], SrcSpan, String)
-> m (HscEnv, [Name], SrcSpan, String)
forall a b. (a -> b) -> a -> b
$ HscEnv
-> ForeignHValue
-> Maybe BreakInfo
-> IO (HscEnv, [Name], SrcSpan, String)
bindLocalsAtBreakpoint HscEnv
hsc_env ForeignHValue
apStack Maybe BreakInfo
mb_info
let ic :: InteractiveContext
ic = HscEnv -> InteractiveContext
hsc_IC HscEnv
hsc_env1
r' :: Resume
r' = Resume
r { resumeHistoryIx :: Int
resumeHistoryIx = Int
new_ix }
ic' :: InteractiveContext
ic' = InteractiveContext
ic { ic_resume :: [Resume]
ic_resume = Resume
r'Resume -> [Resume] -> [Resume]
forall a. a -> [a] -> [a]
:[Resume]
rs }
HscEnv -> m ()
forall (m :: * -> *). GhcMonad m => HscEnv -> m ()
setSession HscEnv
hsc_env1{ hsc_IC :: InteractiveContext
hsc_IC = InteractiveContext
ic' }
([Name], Int, SrcSpan, String) -> m ([Name], Int, SrcSpan, String)
forall (m :: * -> *) a. Monad m => a -> m a
return ([Name]
names, Int
new_ix, SrcSpan
span, String
decl)
if Int
new_ix Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0
then case Resume
r of
Resume { resumeApStack :: Resume -> ForeignHValue
resumeApStack = ForeignHValue
apStack,
resumeBreakInfo :: Resume -> Maybe BreakInfo
resumeBreakInfo = Maybe BreakInfo
mb_brkpt } ->
ForeignHValue
-> Maybe BreakInfo -> m ([Name], Int, SrcSpan, String)
forall {m :: * -> *}.
GhcMonad m =>
ForeignHValue
-> Maybe BreakInfo -> m ([Name], Int, SrcSpan, String)
update_ic ForeignHValue
apStack Maybe BreakInfo
mb_brkpt
else case [History]
history [History] -> Int -> History
forall a. [a] -> Int -> a
!! (Int
new_ix Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) of
History{[String]
ForeignHValue
BreakInfo
historyEnclosingDecls :: [String]
historyBreakInfo :: BreakInfo
historyApStack :: ForeignHValue
historyEnclosingDecls :: History -> [String]
historyApStack :: History -> ForeignHValue
historyBreakInfo :: History -> BreakInfo
..} ->
ForeignHValue
-> Maybe BreakInfo -> m ([Name], Int, SrcSpan, String)
forall {m :: * -> *}.
GhcMonad m =>
ForeignHValue
-> Maybe BreakInfo -> m ([Name], Int, SrcSpan, String)
update_ic ForeignHValue
historyApStack (BreakInfo -> Maybe BreakInfo
forall a. a -> Maybe a
Just BreakInfo
historyBreakInfo)
result_fs :: FastString
result_fs :: FastString
result_fs = String -> FastString
fsLit String
"_result"
bindLocalsAtBreakpoint
:: HscEnv
-> ForeignHValue
-> Maybe BreakInfo
-> IO (HscEnv, [Name], SrcSpan, String)
bindLocalsAtBreakpoint :: HscEnv
-> ForeignHValue
-> Maybe BreakInfo
-> IO (HscEnv, [Name], SrcSpan, String)
bindLocalsAtBreakpoint HscEnv
hsc_env ForeignHValue
apStack Maybe BreakInfo
Nothing = do
let exn_occ :: OccName
exn_occ = FastString -> OccName
mkVarOccFS (String -> FastString
fsLit String
"_exception")
span :: SrcSpan
span = FastString -> SrcSpan
mkGeneralSrcSpan (String -> FastString
fsLit String
"<unknown>")
Name
exn_name <- HscEnv -> OccName -> SrcSpan -> IO Name
newInteractiveBinder HscEnv
hsc_env OccName
exn_occ SrcSpan
span
let e_fs :: FastString
e_fs = String -> FastString
fsLit String
"e"
e_name :: Name
e_name = Unique -> OccName -> SrcSpan -> Name
mkInternalName (FastString -> Unique
forall a. Uniquable a => a -> Unique
getUnique FastString
e_fs) (FastString -> OccName
mkTyVarOccFS FastString
e_fs) SrcSpan
span
e_tyvar :: Id
e_tyvar = Name -> Kind -> Id
mkRuntimeUnkTyVar Name
e_name Kind
liftedTypeKind
exn_id :: Id
exn_id = Name -> Kind -> Id
Id.mkVanillaGlobal Name
exn_name (Id -> Kind
mkTyVarTy Id
e_tyvar)
ictxt0 :: InteractiveContext
ictxt0 = HscEnv -> InteractiveContext
hsc_IC HscEnv
hsc_env
ictxt1 :: InteractiveContext
ictxt1 = InteractiveContext -> [Id] -> InteractiveContext
extendInteractiveContextWithIds InteractiveContext
ictxt0 [Id
exn_id]
dl :: DynLinker
dl = HscEnv -> DynLinker
hsc_dynLinker HscEnv
hsc_env
DynLinker -> [(Name, ForeignHValue)] -> IO ()
Linker.extendLinkEnv DynLinker
dl [(Name
exn_name, ForeignHValue
apStack)]
(HscEnv, [Name], SrcSpan, String)
-> IO (HscEnv, [Name], SrcSpan, String)
forall (m :: * -> *) a. Monad m => a -> m a
return (HscEnv
hsc_env{ hsc_IC :: InteractiveContext
hsc_IC = InteractiveContext
ictxt1 }, [Name
exn_name], SrcSpan
span, String
"<exception thrown>")
bindLocalsAtBreakpoint HscEnv
hsc_env ForeignHValue
apStack_fhv (Just BreakInfo{Int
Module
breakInfo_number :: Int
breakInfo_module :: Module
breakInfo_number :: BreakInfo -> Int
breakInfo_module :: BreakInfo -> Module
..}) = do
let
hmi :: HomeModInfo
hmi = String -> Maybe HomeModInfo -> HomeModInfo
forall a. HasCallStack => String -> Maybe a -> a
expectJust String
"bindLocalsAtBreakpoint" (Maybe HomeModInfo -> HomeModInfo)
-> Maybe HomeModInfo -> HomeModInfo
forall a b. (a -> b) -> a -> b
$
HomePackageTable -> ModuleName -> Maybe HomeModInfo
lookupHpt (HscEnv -> HomePackageTable
hsc_HPT HscEnv
hsc_env) (Module -> ModuleName
forall unit. GenModule unit -> ModuleName
moduleName Module
breakInfo_module)
breaks :: ModBreaks
breaks = HomeModInfo -> ModBreaks
getModBreaks HomeModInfo
hmi
info :: CgBreakInfo
info = String -> Maybe CgBreakInfo -> CgBreakInfo
forall a. HasCallStack => String -> Maybe a -> a
expectJust String
"bindLocalsAtBreakpoint2" (Maybe CgBreakInfo -> CgBreakInfo)
-> Maybe CgBreakInfo -> CgBreakInfo
forall a b. (a -> b) -> a -> b
$
Int -> IntMap CgBreakInfo -> Maybe CgBreakInfo
forall a. Int -> IntMap a -> Maybe a
IntMap.lookup Int
breakInfo_number (ModBreaks -> IntMap CgBreakInfo
modBreaks_breakInfo ModBreaks
breaks)
mbVars :: [Maybe (Id, Word16)]
mbVars = CgBreakInfo -> [Maybe (Id, Word16)]
cgb_vars CgBreakInfo
info
result_ty :: Kind
result_ty = CgBreakInfo -> Kind
cgb_resty CgBreakInfo
info
occs :: [OccName]
occs = ModBreaks -> Array Int [OccName]
modBreaks_vars ModBreaks
breaks Array Int [OccName] -> Int -> [OccName]
forall i e. Ix i => Array i e -> i -> e
! Int
breakInfo_number
span :: SrcSpan
span = ModBreaks -> Array Int SrcSpan
modBreaks_locs ModBreaks
breaks Array Int SrcSpan -> Int -> SrcSpan
forall i e. Ix i => Array i e -> i -> e
! Int
breakInfo_number
decl :: String
decl = String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
intercalate String
"." ([String] -> String) -> [String] -> String
forall a b. (a -> b) -> a -> b
$ ModBreaks -> Array Int [String]
modBreaks_decls ModBreaks
breaks Array Int [String] -> Int -> [String]
forall i e. Ix i => Array i e -> i -> e
! Int
breakInfo_number
mbPointers :: [Maybe (Id, Word16)]
mbPointers = Maybe (Id, Word16) -> Maybe (Id, Word16)
forall {b}. Maybe (Id, b) -> Maybe (Id, b)
nullUnboxed (Maybe (Id, Word16) -> Maybe (Id, Word16))
-> [Maybe (Id, Word16)] -> [Maybe (Id, Word16)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Maybe (Id, Word16)]
mbVars
([Id]
ids, [Word16]
offsets, [OccName]
occs') = [Maybe (Id, Word16)] -> [OccName] -> ([Id], [Word16], [OccName])
forall a b c. [Maybe (a, b)] -> [c] -> ([a], [b], [c])
syncOccs [Maybe (Id, Word16)]
mbPointers [OccName]
occs
free_tvs :: [Id]
free_tvs = [Kind] -> [Id]
tyCoVarsOfTypesList (Kind
result_tyKind -> [Kind] -> [Kind]
forall a. a -> [a] -> [a]
:(Id -> Kind) -> [Id] -> [Kind]
forall a b. (a -> b) -> [a] -> [b]
map Id -> Kind
idType [Id]
ids)
[Maybe ForeignHValue]
mb_hValues <-
(Word16 -> IO (Maybe ForeignHValue))
-> [Word16] -> IO [Maybe ForeignHValue]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (HscEnv -> ForeignHValue -> Int -> IO (Maybe ForeignHValue)
getBreakpointVar HscEnv
hsc_env ForeignHValue
apStack_fhv (Int -> IO (Maybe ForeignHValue))
-> (Word16 -> Int) -> Word16 -> IO (Maybe ForeignHValue)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word16 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) [Word16]
offsets
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when ((Maybe ForeignHValue -> Bool) -> [Maybe ForeignHValue] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any Maybe ForeignHValue -> Bool
forall a. Maybe a -> Bool
isNothing [Maybe ForeignHValue]
mb_hValues) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
DynFlags -> Int -> MsgDoc -> IO ()
debugTraceMsg (HscEnv -> DynFlags
hsc_dflags HscEnv
hsc_env) Int
1 (MsgDoc -> IO ()) -> MsgDoc -> IO ()
forall a b. (a -> b) -> a -> b
$
String -> MsgDoc
text String
"Warning: _result has been evaluated, some bindings have been lost"
UniqSupply
us <- Char -> IO UniqSupply
mkSplitUniqSupply Char
'I'
let tv_subst :: TCvSubst
tv_subst = UniqSupply -> [Id] -> TCvSubst
newTyVars UniqSupply
us [Id]
free_tvs
([Id]
filtered_ids, [OccName]
occs'') = [(Id, OccName)] -> ([Id], [OccName])
forall a b. [(a, b)] -> ([a], [b])
unzip
[ (Id
id, OccName
occ) | (Id
id, Just ForeignHValue
_hv, OccName
occ) <- [Id]
-> [Maybe ForeignHValue]
-> [OccName]
-> [(Id, Maybe ForeignHValue, OccName)]
forall a b c. [a] -> [b] -> [c] -> [(a, b, c)]
zip3 [Id]
ids [Maybe ForeignHValue]
mb_hValues [OccName]
occs' ]
(TidyEnv
_,[Kind]
tidy_tys) = TidyEnv -> [Kind] -> (TidyEnv, [Kind])
tidyOpenTypes TidyEnv
emptyTidyEnv ([Kind] -> (TidyEnv, [Kind])) -> [Kind] -> (TidyEnv, [Kind])
forall a b. (a -> b) -> a -> b
$
(Id -> Kind) -> [Id] -> [Kind]
forall a b. (a -> b) -> [a] -> [b]
map (HasCallStack => TCvSubst -> Kind -> Kind
TCvSubst -> Kind -> Kind
substTy TCvSubst
tv_subst (Kind -> Kind) -> (Id -> Kind) -> Id -> Kind
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Id -> Kind
idType) [Id]
filtered_ids
[Id]
new_ids <- (OccName -> Kind -> Id -> IO Id)
-> [OccName] -> [Kind] -> [Id] -> IO [Id]
forall (m :: * -> *) a b c d.
Monad m =>
(a -> b -> c -> m d) -> [a] -> [b] -> [c] -> m [d]
zipWith3M OccName -> Kind -> Id -> IO Id
mkNewId [OccName]
occs'' [Kind]
tidy_tys [Id]
filtered_ids
Name
result_name <- HscEnv -> OccName -> SrcSpan -> IO Name
newInteractiveBinder HscEnv
hsc_env (FastString -> OccName
mkVarOccFS FastString
result_fs) SrcSpan
span
let result_id :: Id
result_id = Name -> Kind -> Id
Id.mkVanillaGlobal Name
result_name
(HasCallStack => TCvSubst -> Kind -> Kind
TCvSubst -> Kind -> Kind
substTy TCvSubst
tv_subst Kind
result_ty)
result_ok :: Bool
result_ok = Id -> Bool
isPointer Id
result_id
final_ids :: [Id]
final_ids | Bool
result_ok = Id
result_id Id -> [Id] -> [Id]
forall a. a -> [a] -> [a]
: [Id]
new_ids
| Bool
otherwise = [Id]
new_ids
ictxt0 :: InteractiveContext
ictxt0 = HscEnv -> InteractiveContext
hsc_IC HscEnv
hsc_env
ictxt1 :: InteractiveContext
ictxt1 = InteractiveContext -> [Id] -> InteractiveContext
extendInteractiveContextWithIds InteractiveContext
ictxt0 [Id]
final_ids
names :: [Name]
names = (Id -> Name) -> [Id] -> [Name]
forall a b. (a -> b) -> [a] -> [b]
map Id -> Name
idName [Id]
new_ids
dl :: DynLinker
dl = HscEnv -> DynLinker
hsc_dynLinker HscEnv
hsc_env
let fhvs :: [ForeignHValue]
fhvs = [Maybe ForeignHValue] -> [ForeignHValue]
forall a. [Maybe a] -> [a]
catMaybes [Maybe ForeignHValue]
mb_hValues
DynLinker -> [(Name, ForeignHValue)] -> IO ()
Linker.extendLinkEnv DynLinker
dl ([Name] -> [ForeignHValue] -> [(Name, ForeignHValue)]
forall a b. [a] -> [b] -> [(a, b)]
zip [Name]
names [ForeignHValue]
fhvs)
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
result_ok (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ DynLinker -> [(Name, ForeignHValue)] -> IO ()
Linker.extendLinkEnv DynLinker
dl [(Name
result_name, ForeignHValue
apStack_fhv)]
HscEnv
hsc_env1 <- HscEnv -> IO HscEnv
rttiEnvironment HscEnv
hsc_env{ hsc_IC :: InteractiveContext
hsc_IC = InteractiveContext
ictxt1 }
(HscEnv, [Name], SrcSpan, String)
-> IO (HscEnv, [Name], SrcSpan, String)
forall (m :: * -> *) a. Monad m => a -> m a
return (HscEnv
hsc_env1, if Bool
result_ok then Name
result_nameName -> [Name] -> [Name]
forall a. a -> [a] -> [a]
:[Name]
names else [Name]
names, SrcSpan
span, String
decl)
where
mkNewId :: OccName -> Type -> Id -> IO Id
mkNewId :: OccName -> Kind -> Id -> IO Id
mkNewId OccName
occ Kind
ty Id
old_id
= do { Name
name <- HscEnv -> OccName -> SrcSpan -> IO Name
newInteractiveBinder HscEnv
hsc_env OccName
occ (Id -> SrcSpan
forall a. NamedThing a => a -> SrcSpan
getSrcSpan Id
old_id)
; Id -> IO Id
forall (m :: * -> *) a. Monad m => a -> m a
return (Name -> Kind -> IdInfo -> Id
Id.mkVanillaGlobalWithInfo Name
name Kind
ty (HasDebugCallStack => Id -> IdInfo
Id -> IdInfo
idInfo Id
old_id)) }
newTyVars :: UniqSupply -> [TcTyVar] -> TCvSubst
newTyVars :: UniqSupply -> [Id] -> TCvSubst
newTyVars UniqSupply
us [Id]
tvs
= [(Id, Kind)] -> TCvSubst
mkTvSubstPrs [ (Id
tv, Id -> Kind
mkTyVarTy (Name -> Kind -> Id
mkRuntimeUnkTyVar Name
name (Id -> Kind
tyVarKind Id
tv)))
| (Id
tv, Unique
uniq) <- [Id]
tvs [Id] -> [Unique] -> [(Id, Unique)]
forall a b. [a] -> [b] -> [(a, b)]
`zip` UniqSupply -> [Unique]
uniqsFromSupply UniqSupply
us
, let name :: Name
name = Name -> Unique -> Name
setNameUnique (Id -> Name
tyVarName Id
tv) Unique
uniq ]
isPointer :: Id -> Bool
isPointer Id
id | [PrimRep
rep] <- HasDebugCallStack => Kind -> [PrimRep]
Kind -> [PrimRep]
typePrimRep (Id -> Kind
idType Id
id)
, PrimRep -> Bool
isGcPtrRep PrimRep
rep = Bool
True
| Bool
otherwise = Bool
False
nullUnboxed :: Maybe (Id, b) -> Maybe (Id, b)
nullUnboxed (Just (fv :: (Id, b)
fv@(Id
id, b
_)))
| Id -> Bool
isPointer Id
id = (Id, b) -> Maybe (Id, b)
forall a. a -> Maybe a
Just (Id, b)
fv
| Bool
otherwise = Maybe (Id, b)
forall a. Maybe a
Nothing
nullUnboxed Maybe (Id, b)
Nothing = Maybe (Id, b)
forall a. Maybe a
Nothing
syncOccs :: [Maybe (a,b)] -> [c] -> ([a], [b], [c])
syncOccs :: forall a b c. [Maybe (a, b)] -> [c] -> ([a], [b], [c])
syncOccs [Maybe (a, b)]
mbVs [c]
ocs = [(a, b, c)] -> ([a], [b], [c])
forall a b c. [(a, b, c)] -> ([a], [b], [c])
unzip3 ([(a, b, c)] -> ([a], [b], [c])) -> [(a, b, c)] -> ([a], [b], [c])
forall a b. (a -> b) -> a -> b
$ [Maybe (a, b, c)] -> [(a, b, c)]
forall a. [Maybe a] -> [a]
catMaybes ([Maybe (a, b, c)] -> [(a, b, c)])
-> [Maybe (a, b, c)] -> [(a, b, c)]
forall a b. (a -> b) -> a -> b
$ [Maybe (a, b)] -> [c] -> [Maybe (a, b, c)]
forall a b c. [Maybe (a, b)] -> [c] -> [Maybe (a, b, c)]
joinOccs [Maybe (a, b)]
mbVs [c]
ocs
where
joinOccs :: [Maybe (a,b)] -> [c] -> [Maybe (a,b,c)]
joinOccs :: forall a b c. [Maybe (a, b)] -> [c] -> [Maybe (a, b, c)]
joinOccs = String
-> (Maybe (a, b) -> c -> Maybe (a, b, c))
-> [Maybe (a, b)]
-> [c]
-> [Maybe (a, b, c)]
forall a b c. String -> (a -> b -> c) -> [a] -> [b] -> [c]
zipWithEqual String
"bindLocalsAtBreakpoint" Maybe (a, b) -> c -> Maybe (a, b, c)
forall {f :: * -> *} {a} {b} {a}.
Applicative f =>
f (a, b) -> a -> f (a, b, a)
joinOcc
joinOcc :: f (a, b) -> a -> f (a, b, a)
joinOcc f (a, b)
mbV a
oc = (\(a
a,b
b) a
c -> (a
a,b
b,a
c)) ((a, b) -> a -> (a, b, a)) -> f (a, b) -> f (a -> (a, b, a))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> f (a, b)
mbV f (a -> (a, b, a)) -> f a -> f (a, b, a)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure a
oc
rttiEnvironment :: HscEnv -> IO HscEnv
rttiEnvironment :: HscEnv -> IO HscEnv
rttiEnvironment hsc_env :: HscEnv
hsc_env@HscEnv{hsc_IC :: HscEnv -> InteractiveContext
hsc_IC=InteractiveContext
ic} = do
let tmp_ids :: [Id]
tmp_ids = [Id
id | AnId Id
id <- InteractiveContext -> [TyThing]
ic_tythings InteractiveContext
ic]
incompletelyTypedIds :: [Id]
incompletelyTypedIds =
[Id
id | Id
id <- [Id]
tmp_ids
, Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ Id -> Bool
noSkolems Id
id
, (OccName -> FastString
occNameFS(OccName -> FastString) -> (Id -> OccName) -> Id -> FastString
forall b c a. (b -> c) -> (a -> b) -> a -> c
.Name -> OccName
nameOccName(Name -> OccName) -> (Id -> Name) -> Id -> OccName
forall b c a. (b -> c) -> (a -> b) -> a -> c
.Id -> Name
idName) Id
id FastString -> FastString -> Bool
forall a. Eq a => a -> a -> Bool
/= FastString
result_fs]
HscEnv
hsc_env' <- (HscEnv -> Name -> IO HscEnv) -> HscEnv -> [Name] -> IO HscEnv
forall (t :: * -> *) (m :: * -> *) b a.
(Foldable t, Monad m) =>
(b -> a -> m b) -> b -> t a -> m b
foldM HscEnv -> Name -> IO HscEnv
improveTypes HscEnv
hsc_env ((Id -> Name) -> [Id] -> [Name]
forall a b. (a -> b) -> [a] -> [b]
map Id -> Name
idName [Id]
incompletelyTypedIds)
HscEnv -> IO HscEnv
forall (m :: * -> *) a. Monad m => a -> m a
return HscEnv
hsc_env'
where
noSkolems :: Id -> Bool
noSkolems = Kind -> Bool
noFreeVarsOfType (Kind -> Bool) -> (Id -> Kind) -> Id -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Id -> Kind
idType
improveTypes :: HscEnv -> Name -> IO HscEnv
improveTypes hsc_env :: HscEnv
hsc_env@HscEnv{hsc_IC :: HscEnv -> InteractiveContext
hsc_IC=InteractiveContext
ic} Name
name = do
let tmp_ids :: [Id]
tmp_ids = [Id
id | AnId Id
id <- InteractiveContext -> [TyThing]
ic_tythings InteractiveContext
ic]
Just Id
id = (Id -> Bool) -> [Id] -> Maybe Id
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Maybe a
find (\Id
i -> Id -> Name
idName Id
i Name -> Name -> Bool
forall a. Eq a => a -> a -> Bool
== Name
name) [Id]
tmp_ids
if Id -> Bool
noSkolems Id
id
then HscEnv -> IO HscEnv
forall (m :: * -> *) a. Monad m => a -> m a
return HscEnv
hsc_env
else do
Maybe Kind
mb_new_ty <- HscEnv -> Int -> Id -> IO (Maybe Kind)
reconstructType HscEnv
hsc_env Int
10 Id
id
let old_ty :: Kind
old_ty = Id -> Kind
idType Id
id
case Maybe Kind
mb_new_ty of
Maybe Kind
Nothing -> HscEnv -> IO HscEnv
forall (m :: * -> *) a. Monad m => a -> m a
return HscEnv
hsc_env
Just Kind
new_ty -> do
case HscEnv -> Kind -> Kind -> Maybe TCvSubst
improveRTTIType HscEnv
hsc_env Kind
old_ty Kind
new_ty of
Maybe TCvSubst
Nothing -> HscEnv -> IO HscEnv
forall (m :: * -> *) a. Monad m => a -> m a
return (HscEnv -> IO HscEnv) -> HscEnv -> IO HscEnv
forall a b. (a -> b) -> a -> b
$
WARN(True, text (":print failed to calculate the "
++ "improvement for a type")) hsc_env
Just TCvSubst
subst -> do
let dflags :: DynFlags
dflags = HscEnv -> DynFlags
hsc_dflags HscEnv
hsc_env
DynFlags -> DumpFlag -> String -> DumpFormat -> MsgDoc -> IO ()
dumpIfSet_dyn DynFlags
dflags DumpFlag
Opt_D_dump_rtti String
"RTTI"
DumpFormat
FormatText
([MsgDoc] -> MsgDoc
fsep [String -> MsgDoc
text String
"RTTI Improvement for", Id -> MsgDoc
forall a. Outputable a => a -> MsgDoc
ppr Id
id, MsgDoc
equals,
TCvSubst -> MsgDoc
forall a. Outputable a => a -> MsgDoc
ppr TCvSubst
subst])
let ic' :: InteractiveContext
ic' = InteractiveContext -> TCvSubst -> InteractiveContext
substInteractiveContext InteractiveContext
ic TCvSubst
subst
HscEnv -> IO HscEnv
forall (m :: * -> *) a. Monad m => a -> m a
return HscEnv
hsc_env{hsc_IC :: InteractiveContext
hsc_IC=InteractiveContext
ic'}
pushResume :: HscEnv -> Resume -> HscEnv
pushResume :: HscEnv -> Resume -> HscEnv
pushResume HscEnv
hsc_env Resume
resume = HscEnv
hsc_env { hsc_IC :: InteractiveContext
hsc_IC = InteractiveContext
ictxt1 }
where
ictxt0 :: InteractiveContext
ictxt0 = HscEnv -> InteractiveContext
hsc_IC HscEnv
hsc_env
ictxt1 :: InteractiveContext
ictxt1 = InteractiveContext
ictxt0 { ic_resume :: [Resume]
ic_resume = Resume
resume Resume -> [Resume] -> [Resume]
forall a. a -> [a] -> [a]
: InteractiveContext -> [Resume]
ic_resume InteractiveContext
ictxt0 }
abandon :: GhcMonad m => m Bool
abandon :: forall (m :: * -> *). GhcMonad m => m Bool
abandon = do
HscEnv
hsc_env <- m HscEnv
forall (m :: * -> *). GhcMonad m => m HscEnv
getSession
let ic :: InteractiveContext
ic = HscEnv -> InteractiveContext
hsc_IC HscEnv
hsc_env
resume :: [Resume]
resume = InteractiveContext -> [Resume]
ic_resume InteractiveContext
ic
case [Resume]
resume of
[] -> Bool -> m Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
False
Resume
r:[Resume]
rs -> do
HscEnv -> m ()
forall (m :: * -> *). GhcMonad m => HscEnv -> m ()
setSession HscEnv
hsc_env{ hsc_IC :: InteractiveContext
hsc_IC = InteractiveContext
ic { ic_resume :: [Resume]
ic_resume = [Resume]
rs } }
IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ HscEnv -> ForeignRef (ResumeContext [HValueRef]) -> IO ()
abandonStmt HscEnv
hsc_env (Resume -> ForeignRef (ResumeContext [HValueRef])
resumeContext Resume
r)
Bool -> m Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
True
abandonAll :: GhcMonad m => m Bool
abandonAll :: forall (m :: * -> *). GhcMonad m => m Bool
abandonAll = do
HscEnv
hsc_env <- m HscEnv
forall (m :: * -> *). GhcMonad m => m HscEnv
getSession
let ic :: InteractiveContext
ic = HscEnv -> InteractiveContext
hsc_IC HscEnv
hsc_env
resume :: [Resume]
resume = InteractiveContext -> [Resume]
ic_resume InteractiveContext
ic
case [Resume]
resume of
[] -> Bool -> m Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
False
[Resume]
rs -> do
HscEnv -> m ()
forall (m :: * -> *). GhcMonad m => HscEnv -> m ()
setSession HscEnv
hsc_env{ hsc_IC :: InteractiveContext
hsc_IC = InteractiveContext
ic { ic_resume :: [Resume]
ic_resume = [] } }
IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ (Resume -> IO ()) -> [Resume] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (HscEnv -> ForeignRef (ResumeContext [HValueRef]) -> IO ()
abandonStmt HscEnv
hsc_env(ForeignRef (ResumeContext [HValueRef]) -> IO ())
-> (Resume -> ForeignRef (ResumeContext [HValueRef]))
-> Resume
-> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Resume -> ForeignRef (ResumeContext [HValueRef])
resumeContext) [Resume]
rs
Bool -> m Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
True
data BoundedList a = BL
{-# UNPACK #-} !Int
{-# UNPACK #-} !Int
[a]
[a]
nilBL :: Int -> BoundedList a
nilBL :: forall a. Int -> BoundedList a
nilBL Int
bound = Int -> Int -> [a] -> [a] -> BoundedList a
forall a. Int -> Int -> [a] -> [a] -> BoundedList a
BL Int
0 Int
bound [] []
consBL :: a -> BoundedList a -> BoundedList a
consBL :: forall a. a -> BoundedList a -> BoundedList a
consBL a
a (BL Int
len Int
bound [a]
left [a]
right)
| Int
len Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
bound = Int -> Int -> [a] -> [a] -> BoundedList a
forall a. Int -> Int -> [a] -> [a] -> BoundedList a
BL (Int
lenInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1) Int
bound (a
aa -> [a] -> [a]
forall a. a -> [a] -> [a]
:[a]
left) [a]
right
| [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [a]
right = Int -> Int -> [a] -> [a] -> BoundedList a
forall a. Int -> Int -> [a] -> [a] -> BoundedList a
BL Int
len Int
bound [a
a] ([a] -> BoundedList a) -> [a] -> BoundedList a
forall a b. (a -> b) -> a -> b
$! [a] -> [a]
forall a. [a] -> [a]
tail ([a] -> [a]
forall a. [a] -> [a]
reverse [a]
left)
| Bool
otherwise = Int -> Int -> [a] -> [a] -> BoundedList a
forall a. Int -> Int -> [a] -> [a] -> BoundedList a
BL Int
len Int
bound (a
aa -> [a] -> [a]
forall a. a -> [a] -> [a]
:[a]
left) ([a] -> BoundedList a) -> [a] -> BoundedList a
forall a b. (a -> b) -> a -> b
$! [a] -> [a]
forall a. [a] -> [a]
tail [a]
right
toListBL :: BoundedList a -> [a]
toListBL :: forall a. BoundedList a -> [a]
toListBL (BL Int
_ Int
_ [a]
left [a]
right) = [a]
left [a] -> [a] -> [a]
forall a. [a] -> [a] -> [a]
++ [a] -> [a]
forall a. [a] -> [a]
reverse [a]
right
fromListBL :: Int -> [a] -> BoundedList a
fromListBL :: forall a. Int -> [a] -> BoundedList a
fromListBL Int
bound [a]
l = Int -> Int -> [a] -> [a] -> BoundedList a
forall a. Int -> Int -> [a] -> [a] -> BoundedList a
BL ([a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [a]
l) Int
bound [a]
l []
setContext :: GhcMonad m => [InteractiveImport] -> m ()
setContext :: forall (m :: * -> *). GhcMonad m => [InteractiveImport] -> m ()
setContext [InteractiveImport]
imports
= do { HscEnv
hsc_env <- m HscEnv
forall (m :: * -> *). GhcMonad m => m HscEnv
getSession
; let dflags :: DynFlags
dflags = HscEnv -> DynFlags
hsc_dflags HscEnv
hsc_env
; Either (ModuleName, String) GlobalRdrEnv
all_env_err <- IO (Either (ModuleName, String) GlobalRdrEnv)
-> m (Either (ModuleName, String) GlobalRdrEnv)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Either (ModuleName, String) GlobalRdrEnv)
-> m (Either (ModuleName, String) GlobalRdrEnv))
-> IO (Either (ModuleName, String) GlobalRdrEnv)
-> m (Either (ModuleName, String) GlobalRdrEnv)
forall a b. (a -> b) -> a -> b
$ HscEnv
-> [InteractiveImport]
-> IO (Either (ModuleName, String) GlobalRdrEnv)
findGlobalRdrEnv HscEnv
hsc_env [InteractiveImport]
imports
; case Either (ModuleName, String) GlobalRdrEnv
all_env_err of
Left (ModuleName
mod, String
err) ->
IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ GhcException -> IO ()
forall a. GhcException -> IO a
throwGhcExceptionIO (DynFlags -> ModuleName -> String -> GhcException
forall {a}. Outputable a => DynFlags -> a -> String -> GhcException
formatError DynFlags
dflags ModuleName
mod String
err)
Right GlobalRdrEnv
all_env -> do {
; let old_ic :: InteractiveContext
old_ic = HscEnv -> InteractiveContext
hsc_IC HscEnv
hsc_env
!final_rdr_env :: GlobalRdrEnv
final_rdr_env = GlobalRdrEnv
all_env GlobalRdrEnv -> [TyThing] -> GlobalRdrEnv
`icExtendGblRdrEnv` InteractiveContext -> [TyThing]
ic_tythings InteractiveContext
old_ic
; HscEnv -> m ()
forall (m :: * -> *). GhcMonad m => HscEnv -> m ()
setSession
HscEnv
hsc_env{ hsc_IC :: InteractiveContext
hsc_IC = InteractiveContext
old_ic { ic_imports :: [InteractiveImport]
ic_imports = [InteractiveImport]
imports
, ic_rn_gbl_env :: GlobalRdrEnv
ic_rn_gbl_env = GlobalRdrEnv
final_rdr_env }}}}
where
formatError :: DynFlags -> a -> String -> GhcException
formatError DynFlags
dflags a
mod String
err = String -> GhcException
ProgramError (String -> GhcException)
-> (MsgDoc -> String) -> MsgDoc -> GhcException
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DynFlags -> MsgDoc -> String
showSDoc DynFlags
dflags (MsgDoc -> GhcException) -> MsgDoc -> GhcException
forall a b. (a -> b) -> a -> b
$
String -> MsgDoc
text String
"Cannot add module" MsgDoc -> MsgDoc -> MsgDoc
<+> a -> MsgDoc
forall a. Outputable a => a -> MsgDoc
ppr a
mod MsgDoc -> MsgDoc -> MsgDoc
<+>
String -> MsgDoc
text String
"to context:" MsgDoc -> MsgDoc -> MsgDoc
<+> String -> MsgDoc
text String
err
findGlobalRdrEnv :: HscEnv -> [InteractiveImport]
-> IO (Either (ModuleName, String) GlobalRdrEnv)
findGlobalRdrEnv :: HscEnv
-> [InteractiveImport]
-> IO (Either (ModuleName, String) GlobalRdrEnv)
findGlobalRdrEnv HscEnv
hsc_env [InteractiveImport]
imports
= do { GlobalRdrEnv
idecls_env <- HscEnv -> [LImportDecl GhcPs] -> IO GlobalRdrEnv
hscRnImportDecls HscEnv
hsc_env [LImportDecl GhcPs]
idecls
; Either (ModuleName, String) GlobalRdrEnv
-> IO (Either (ModuleName, String) GlobalRdrEnv)
forall (m :: * -> *) a. Monad m => a -> m a
return (Either (ModuleName, String) GlobalRdrEnv
-> IO (Either (ModuleName, String) GlobalRdrEnv))
-> Either (ModuleName, String) GlobalRdrEnv
-> IO (Either (ModuleName, String) GlobalRdrEnv)
forall a b. (a -> b) -> a -> b
$ case [Either (ModuleName, String) GlobalRdrEnv]
-> ([(ModuleName, String)], [GlobalRdrEnv])
forall a b. [Either a b] -> ([a], [b])
partitionEithers ((ModuleName -> Either (ModuleName, String) GlobalRdrEnv)
-> [ModuleName] -> [Either (ModuleName, String) GlobalRdrEnv]
forall a b. (a -> b) -> [a] -> [b]
map ModuleName -> Either (ModuleName, String) GlobalRdrEnv
mkEnv [ModuleName]
imods) of
([], [GlobalRdrEnv]
imods_env) -> GlobalRdrEnv -> Either (ModuleName, String) GlobalRdrEnv
forall a b. b -> Either a b
Right ((GlobalRdrEnv -> GlobalRdrEnv -> GlobalRdrEnv)
-> GlobalRdrEnv -> [GlobalRdrEnv] -> GlobalRdrEnv
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr GlobalRdrEnv -> GlobalRdrEnv -> GlobalRdrEnv
plusGlobalRdrEnv GlobalRdrEnv
idecls_env [GlobalRdrEnv]
imods_env)
((ModuleName, String)
err : [(ModuleName, String)]
_, [GlobalRdrEnv]
_) -> (ModuleName, String) -> Either (ModuleName, String) GlobalRdrEnv
forall a b. a -> Either a b
Left (ModuleName, String)
err }
where
idecls :: [LImportDecl GhcPs]
idecls :: [LImportDecl GhcPs]
idecls = [ImportDecl GhcPs -> LImportDecl GhcPs
forall e. e -> Located e
noLoc ImportDecl GhcPs
d | IIDecl ImportDecl GhcPs
d <- [InteractiveImport]
imports]
imods :: [ModuleName]
imods :: [ModuleName]
imods = [ModuleName
m | IIModule ModuleName
m <- [InteractiveImport]
imports]
mkEnv :: ModuleName -> Either (ModuleName, String) GlobalRdrEnv
mkEnv ModuleName
mod = case HomePackageTable -> ModuleName -> Either String GlobalRdrEnv
mkTopLevEnv (HscEnv -> HomePackageTable
hsc_HPT HscEnv
hsc_env) ModuleName
mod of
Left String
err -> (ModuleName, String) -> Either (ModuleName, String) GlobalRdrEnv
forall a b. a -> Either a b
Left (ModuleName
mod, String
err)
Right GlobalRdrEnv
env -> GlobalRdrEnv -> Either (ModuleName, String) GlobalRdrEnv
forall a b. b -> Either a b
Right GlobalRdrEnv
env
availsToGlobalRdrEnv :: ModuleName -> [AvailInfo] -> GlobalRdrEnv
availsToGlobalRdrEnv :: ModuleName -> [AvailInfo] -> GlobalRdrEnv
availsToGlobalRdrEnv ModuleName
mod_name [AvailInfo]
avails
= [GlobalRdrElt] -> GlobalRdrEnv
mkGlobalRdrEnv (Maybe ImportSpec -> [AvailInfo] -> [GlobalRdrElt]
gresFromAvails (ImportSpec -> Maybe ImportSpec
forall a. a -> Maybe a
Just ImportSpec
imp_spec) [AvailInfo]
avails)
where
imp_spec :: ImportSpec
imp_spec = ImpSpec :: ImpDeclSpec -> ImpItemSpec -> ImportSpec
ImpSpec { is_decl :: ImpDeclSpec
is_decl = ImpDeclSpec
decl, is_item :: ImpItemSpec
is_item = ImpItemSpec
ImpAll}
decl :: ImpDeclSpec
decl = ImpDeclSpec :: ModuleName -> ModuleName -> Bool -> SrcSpan -> ImpDeclSpec
ImpDeclSpec { is_mod :: ModuleName
is_mod = ModuleName
mod_name, is_as :: ModuleName
is_as = ModuleName
mod_name,
is_qual :: Bool
is_qual = Bool
False,
is_dloc :: SrcSpan
is_dloc = SrcLoc -> SrcSpan
srcLocSpan SrcLoc
interactiveSrcLoc }
mkTopLevEnv :: HomePackageTable -> ModuleName -> Either String GlobalRdrEnv
mkTopLevEnv :: HomePackageTable -> ModuleName -> Either String GlobalRdrEnv
mkTopLevEnv HomePackageTable
hpt ModuleName
modl
= case HomePackageTable -> ModuleName -> Maybe HomeModInfo
lookupHpt HomePackageTable
hpt ModuleName
modl of
Maybe HomeModInfo
Nothing -> String -> Either String GlobalRdrEnv
forall a b. a -> Either a b
Left String
"not a home module"
Just HomeModInfo
details ->
case ModIface_ 'ModIfaceFinal -> Maybe GlobalRdrEnv
forall (phase :: ModIfacePhase).
ModIface_ phase -> Maybe GlobalRdrEnv
mi_globals (HomeModInfo -> ModIface_ 'ModIfaceFinal
hm_iface HomeModInfo
details) of
Maybe GlobalRdrEnv
Nothing -> String -> Either String GlobalRdrEnv
forall a b. a -> Either a b
Left String
"not interpreted"
Just GlobalRdrEnv
env -> GlobalRdrEnv -> Either String GlobalRdrEnv
forall a b. b -> Either a b
Right GlobalRdrEnv
env
getContext :: GhcMonad m => m [InteractiveImport]
getContext :: forall (m :: * -> *). GhcMonad m => m [InteractiveImport]
getContext = (HscEnv -> m [InteractiveImport]) -> m [InteractiveImport]
forall (m :: * -> *) a. GhcMonad m => (HscEnv -> m a) -> m a
withSession ((HscEnv -> m [InteractiveImport]) -> m [InteractiveImport])
-> (HscEnv -> m [InteractiveImport]) -> m [InteractiveImport]
forall a b. (a -> b) -> a -> b
$ \HscEnv{ hsc_IC :: HscEnv -> InteractiveContext
hsc_IC=InteractiveContext
ic } ->
[InteractiveImport] -> m [InteractiveImport]
forall (m :: * -> *) a. Monad m => a -> m a
return (InteractiveContext -> [InteractiveImport]
ic_imports InteractiveContext
ic)
moduleIsInterpreted :: GhcMonad m => Module -> m Bool
moduleIsInterpreted :: forall (m :: * -> *). GhcMonad m => Module -> m Bool
moduleIsInterpreted Module
modl = (HscEnv -> m Bool) -> m Bool
forall (m :: * -> *) a. GhcMonad m => (HscEnv -> m a) -> m a
withSession ((HscEnv -> m Bool) -> m Bool) -> (HscEnv -> m Bool) -> m Bool
forall a b. (a -> b) -> a -> b
$ \HscEnv
h ->
if Bool -> Bool
not (DynFlags -> Module -> Bool
isHomeModule (HscEnv -> DynFlags
hsc_dflags HscEnv
h) Module
modl)
then Bool -> m Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
False
else case HomePackageTable -> ModuleName -> Maybe HomeModInfo
lookupHpt (HscEnv -> HomePackageTable
hsc_HPT HscEnv
h) (Module -> ModuleName
forall unit. GenModule unit -> ModuleName
moduleName Module
modl) of
Just HomeModInfo
details -> Bool -> m Bool
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe GlobalRdrEnv -> Bool
forall a. Maybe a -> Bool
isJust (ModIface_ 'ModIfaceFinal -> Maybe GlobalRdrEnv
forall (phase :: ModIfacePhase).
ModIface_ phase -> Maybe GlobalRdrEnv
mi_globals (HomeModInfo -> ModIface_ 'ModIfaceFinal
hm_iface HomeModInfo
details)))
Maybe HomeModInfo
_not_a_home_module -> Bool -> m Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
False
getInfo :: GhcMonad m => Bool -> Name
-> m (Maybe (TyThing,Fixity,[ClsInst],[FamInst], SDoc))
getInfo :: forall (m :: * -> *).
GhcMonad m =>
Bool
-> Name
-> m (Maybe (TyThing, Fixity, [ClsInst], [FamInst], MsgDoc))
getInfo Bool
allInfo Name
name
= (HscEnv
-> m (Maybe (TyThing, Fixity, [ClsInst], [FamInst], MsgDoc)))
-> m (Maybe (TyThing, Fixity, [ClsInst], [FamInst], MsgDoc))
forall (m :: * -> *) a. GhcMonad m => (HscEnv -> m a) -> m a
withSession ((HscEnv
-> m (Maybe (TyThing, Fixity, [ClsInst], [FamInst], MsgDoc)))
-> m (Maybe (TyThing, Fixity, [ClsInst], [FamInst], MsgDoc)))
-> (HscEnv
-> m (Maybe (TyThing, Fixity, [ClsInst], [FamInst], MsgDoc)))
-> m (Maybe (TyThing, Fixity, [ClsInst], [FamInst], MsgDoc))
forall a b. (a -> b) -> a -> b
$ \HscEnv
hsc_env ->
do Maybe (TyThing, Fixity, [ClsInst], [FamInst], MsgDoc)
mb_stuff <- IO (Maybe (TyThing, Fixity, [ClsInst], [FamInst], MsgDoc))
-> m (Maybe (TyThing, Fixity, [ClsInst], [FamInst], MsgDoc))
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe (TyThing, Fixity, [ClsInst], [FamInst], MsgDoc))
-> m (Maybe (TyThing, Fixity, [ClsInst], [FamInst], MsgDoc)))
-> IO (Maybe (TyThing, Fixity, [ClsInst], [FamInst], MsgDoc))
-> m (Maybe (TyThing, Fixity, [ClsInst], [FamInst], MsgDoc))
forall a b. (a -> b) -> a -> b
$ HscEnv
-> Name
-> IO (Maybe (TyThing, Fixity, [ClsInst], [FamInst], MsgDoc))
hscTcRnGetInfo HscEnv
hsc_env Name
name
case Maybe (TyThing, Fixity, [ClsInst], [FamInst], MsgDoc)
mb_stuff of
Maybe (TyThing, Fixity, [ClsInst], [FamInst], MsgDoc)
Nothing -> Maybe (TyThing, Fixity, [ClsInst], [FamInst], MsgDoc)
-> m (Maybe (TyThing, Fixity, [ClsInst], [FamInst], MsgDoc))
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe (TyThing, Fixity, [ClsInst], [FamInst], MsgDoc)
forall a. Maybe a
Nothing
Just (TyThing
thing, Fixity
fixity, [ClsInst]
cls_insts, [FamInst]
fam_insts, MsgDoc
docs) -> do
let rdr_env :: GlobalRdrEnv
rdr_env = InteractiveContext -> GlobalRdrEnv
ic_rn_gbl_env (HscEnv -> InteractiveContext
hsc_IC HscEnv
hsc_env)
let cls_insts' :: [ClsInst]
cls_insts' = (ClsInst -> Bool) -> [ClsInst] -> [ClsInst]
forall a. (a -> Bool) -> [a] -> [a]
filter (GlobalRdrEnv -> NameSet -> Bool
plausible GlobalRdrEnv
rdr_env (NameSet -> Bool) -> (ClsInst -> NameSet) -> ClsInst -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ClsInst -> NameSet
orphNamesOfClsInst) [ClsInst]
cls_insts
fam_insts' :: [FamInst]
fam_insts' = (FamInst -> Bool) -> [FamInst] -> [FamInst]
forall a. (a -> Bool) -> [a] -> [a]
filter (GlobalRdrEnv -> NameSet -> Bool
plausible GlobalRdrEnv
rdr_env (NameSet -> Bool) -> (FamInst -> NameSet) -> FamInst -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FamInst -> NameSet
orphNamesOfFamInst) [FamInst]
fam_insts
Maybe (TyThing, Fixity, [ClsInst], [FamInst], MsgDoc)
-> m (Maybe (TyThing, Fixity, [ClsInst], [FamInst], MsgDoc))
forall (m :: * -> *) a. Monad m => a -> m a
return ((TyThing, Fixity, [ClsInst], [FamInst], MsgDoc)
-> Maybe (TyThing, Fixity, [ClsInst], [FamInst], MsgDoc)
forall a. a -> Maybe a
Just (TyThing
thing, Fixity
fixity, [ClsInst]
cls_insts', [FamInst]
fam_insts', MsgDoc
docs))
where
plausible :: GlobalRdrEnv -> NameSet -> Bool
plausible GlobalRdrEnv
rdr_env NameSet
names
= Bool
allInfo
Bool -> Bool -> Bool
|| (Name -> Bool) -> NameSet -> Bool
nameSetAll Name -> Bool
ok NameSet
names
where
ok :: Name -> Bool
ok Name
n | Name
n Name -> Name -> Bool
forall a. Eq a => a -> a -> Bool
== Name
name = Bool
True
| Name -> Bool
pretendNameIsInScope Name
n = Bool
True
| Name -> Bool
isBuiltInSyntax Name
n = Bool
True
| Name -> Bool
isCTupleTyConName Name
n = Bool
True
| Name -> Bool
isExternalName Name
n = Maybe GlobalRdrElt -> Bool
forall a. Maybe a -> Bool
isJust (GlobalRdrEnv -> Name -> Maybe GlobalRdrElt
lookupGRE_Name GlobalRdrEnv
rdr_env Name
n)
| Bool
otherwise = Bool
True
getNamesInScope :: GhcMonad m => m [Name]
getNamesInScope :: forall (m :: * -> *). GhcMonad m => m [Name]
getNamesInScope = (HscEnv -> m [Name]) -> m [Name]
forall (m :: * -> *) a. GhcMonad m => (HscEnv -> m a) -> m a
withSession ((HscEnv -> m [Name]) -> m [Name])
-> (HscEnv -> m [Name]) -> m [Name]
forall a b. (a -> b) -> a -> b
$ \HscEnv
hsc_env -> do
[Name] -> m [Name]
forall (m :: * -> *) a. Monad m => a -> m a
return ((GlobalRdrElt -> Name) -> [GlobalRdrElt] -> [Name]
forall a b. (a -> b) -> [a] -> [b]
map GlobalRdrElt -> Name
gre_name (GlobalRdrEnv -> [GlobalRdrElt]
globalRdrEnvElts (InteractiveContext -> GlobalRdrEnv
ic_rn_gbl_env (HscEnv -> InteractiveContext
hsc_IC HscEnv
hsc_env))))
getRdrNamesInScope :: GhcMonad m => m [RdrName]
getRdrNamesInScope :: forall (m :: * -> *). GhcMonad m => m [RdrName]
getRdrNamesInScope = (HscEnv -> m [RdrName]) -> m [RdrName]
forall (m :: * -> *) a. GhcMonad m => (HscEnv -> m a) -> m a
withSession ((HscEnv -> m [RdrName]) -> m [RdrName])
-> (HscEnv -> m [RdrName]) -> m [RdrName]
forall a b. (a -> b) -> a -> b
$ \HscEnv
hsc_env -> do
let
ic :: InteractiveContext
ic = HscEnv -> InteractiveContext
hsc_IC HscEnv
hsc_env
gbl_rdrenv :: GlobalRdrEnv
gbl_rdrenv = InteractiveContext -> GlobalRdrEnv
ic_rn_gbl_env InteractiveContext
ic
gbl_names :: [RdrName]
gbl_names = (GlobalRdrElt -> [RdrName]) -> [GlobalRdrElt] -> [RdrName]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap GlobalRdrElt -> [RdrName]
greRdrNames ([GlobalRdrElt] -> [RdrName]) -> [GlobalRdrElt] -> [RdrName]
forall a b. (a -> b) -> a -> b
$ GlobalRdrEnv -> [GlobalRdrElt]
globalRdrEnvElts GlobalRdrEnv
gbl_rdrenv
[RdrName] -> m [RdrName]
forall (m :: * -> *) a. Monad m => a -> m a
return ((RdrName -> Bool) -> [RdrName] -> [RdrName]
forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not (Bool -> Bool) -> (RdrName -> Bool) -> RdrName -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. OccName -> Bool
isDerivedOccName (OccName -> Bool) -> (RdrName -> OccName) -> RdrName -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RdrName -> OccName
rdrNameOcc) [RdrName]
gbl_names)
parseName :: GhcMonad m => String -> m [Name]
parseName :: forall (m :: * -> *). GhcMonad m => String -> m [Name]
parseName String
str = (HscEnv -> m [Name]) -> m [Name]
forall (m :: * -> *) a. GhcMonad m => (HscEnv -> m a) -> m a
withSession ((HscEnv -> m [Name]) -> m [Name])
-> (HscEnv -> m [Name]) -> m [Name]
forall a b. (a -> b) -> a -> b
$ \HscEnv
hsc_env -> IO [Name] -> m [Name]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [Name] -> m [Name]) -> IO [Name] -> m [Name]
forall a b. (a -> b) -> a -> b
$
do { Located RdrName
lrdr_name <- HscEnv -> String -> IO (Located RdrName)
hscParseIdentifier HscEnv
hsc_env String
str
; HscEnv -> Located RdrName -> IO [Name]
hscTcRnLookupRdrName HscEnv
hsc_env Located RdrName
lrdr_name }
isStmt :: ParserFlags -> String -> Bool
isStmt :: ParserFlags -> String -> Bool
isStmt ParserFlags
pflags String
stmt =
case P (Maybe (GhciLStmt GhcPs))
-> ParserFlags -> String -> ParseResult (Maybe (GhciLStmt GhcPs))
forall thing. P thing -> ParserFlags -> String -> ParseResult thing
parseThing P (Maybe (GhciLStmt GhcPs))
Parser.parseStmt ParserFlags
pflags String
stmt of
Lexer.POk PState
_ Maybe (GhciLStmt GhcPs)
_ -> Bool
True
Lexer.PFailed PState
_ -> Bool
False
hasImport :: ParserFlags -> String -> Bool
hasImport :: ParserFlags -> String -> Bool
hasImport ParserFlags
pflags String
stmt =
case P (Located HsModule)
-> ParserFlags -> String -> ParseResult (Located HsModule)
forall thing. P thing -> ParserFlags -> String -> ParseResult thing
parseThing P (Located HsModule)
Parser.parseModule ParserFlags
pflags String
stmt of
Lexer.POk PState
_ Located HsModule
thing -> Located HsModule -> Bool
forall {l}. GenLocated l HsModule -> Bool
hasImports Located HsModule
thing
Lexer.PFailed PState
_ -> Bool
False
where
hasImports :: GenLocated l HsModule -> Bool
hasImports = Bool -> Bool
not (Bool -> Bool)
-> (GenLocated l HsModule -> Bool) -> GenLocated l HsModule -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [LImportDecl GhcPs] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null ([LImportDecl GhcPs] -> Bool)
-> (GenLocated l HsModule -> [LImportDecl GhcPs])
-> GenLocated l HsModule
-> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HsModule -> [LImportDecl GhcPs]
hsmodImports (HsModule -> [LImportDecl GhcPs])
-> (GenLocated l HsModule -> HsModule)
-> GenLocated l HsModule
-> [LImportDecl GhcPs]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GenLocated l HsModule -> HsModule
forall l e. GenLocated l e -> e
unLoc
isImport :: ParserFlags -> String -> Bool
isImport :: ParserFlags -> String -> Bool
isImport ParserFlags
pflags String
stmt =
case P (LImportDecl GhcPs)
-> ParserFlags -> String -> ParseResult (LImportDecl GhcPs)
forall thing. P thing -> ParserFlags -> String -> ParseResult thing
parseThing P (LImportDecl GhcPs)
Parser.parseImport ParserFlags
pflags String
stmt of
Lexer.POk PState
_ LImportDecl GhcPs
_ -> Bool
True
Lexer.PFailed PState
_ -> Bool
False
isDecl :: ParserFlags -> String -> Bool
isDecl :: ParserFlags -> String -> Bool
isDecl ParserFlags
pflags String
stmt = do
case P (LHsDecl GhcPs)
-> ParserFlags -> String -> ParseResult (LHsDecl GhcPs)
forall thing. P thing -> ParserFlags -> String -> ParseResult thing
parseThing P (LHsDecl GhcPs)
Parser.parseDeclaration ParserFlags
pflags String
stmt of
Lexer.POk PState
_ LHsDecl GhcPs
thing ->
case LHsDecl GhcPs -> HsDecl GhcPs
forall l e. GenLocated l e -> e
unLoc LHsDecl GhcPs
thing of
SpliceD XSpliceD GhcPs
_ SpliceDecl GhcPs
_ -> Bool
False
HsDecl GhcPs
_ -> Bool
True
Lexer.PFailed PState
_ -> Bool
False
parseThing :: Lexer.P thing -> ParserFlags -> String -> Lexer.ParseResult thing
parseThing :: forall thing. P thing -> ParserFlags -> String -> ParseResult thing
parseThing P thing
parser ParserFlags
pflags String
stmt = do
let buf :: StringBuffer
buf = String -> StringBuffer
stringToStringBuffer String
stmt
loc :: RealSrcLoc
loc = FastString -> Int -> Int -> RealSrcLoc
mkRealSrcLoc (String -> FastString
fsLit String
"<interactive>") Int
1 Int
1
P thing -> PState -> ParseResult thing
forall a. P a -> PState -> ParseResult a
Lexer.unP P thing
parser (ParserFlags -> StringBuffer -> RealSrcLoc -> PState
Lexer.mkPStatePure ParserFlags
pflags StringBuffer
buf RealSrcLoc
loc)
getDocs :: GhcMonad m
=> Name
-> m (Either GetDocsFailure (Maybe HsDocString, Map Int HsDocString))
getDocs :: forall (m :: * -> *).
GhcMonad m =>
Name
-> m (Either
GetDocsFailure (Maybe HsDocString, Map Int HsDocString))
getDocs Name
name =
(HscEnv
-> m (Either
GetDocsFailure (Maybe HsDocString, Map Int HsDocString)))
-> m (Either
GetDocsFailure (Maybe HsDocString, Map Int HsDocString))
forall (m :: * -> *) a. GhcMonad m => (HscEnv -> m a) -> m a
withSession ((HscEnv
-> m (Either
GetDocsFailure (Maybe HsDocString, Map Int HsDocString)))
-> m (Either
GetDocsFailure (Maybe HsDocString, Map Int HsDocString)))
-> (HscEnv
-> m (Either
GetDocsFailure (Maybe HsDocString, Map Int HsDocString)))
-> m (Either
GetDocsFailure (Maybe HsDocString, Map Int HsDocString))
forall a b. (a -> b) -> a -> b
$ \HscEnv
hsc_env -> do
case Name -> Maybe Module
nameModule_maybe Name
name of
Maybe Module
Nothing -> Either GetDocsFailure (Maybe HsDocString, Map Int HsDocString)
-> m (Either
GetDocsFailure (Maybe HsDocString, Map Int HsDocString))
forall (f :: * -> *) a. Applicative f => a -> f a
pure (GetDocsFailure
-> Either GetDocsFailure (Maybe HsDocString, Map Int HsDocString)
forall a b. a -> Either a b
Left (Name -> GetDocsFailure
NameHasNoModule Name
name))
Just Module
mod -> do
if Module -> Bool
isInteractiveModule Module
mod
then Either GetDocsFailure (Maybe HsDocString, Map Int HsDocString)
-> m (Either
GetDocsFailure (Maybe HsDocString, Map Int HsDocString))
forall (f :: * -> *) a. Applicative f => a -> f a
pure (GetDocsFailure
-> Either GetDocsFailure (Maybe HsDocString, Map Int HsDocString)
forall a b. a -> Either a b
Left GetDocsFailure
InteractiveName)
else do
ModIface { mi_doc_hdr :: forall (phase :: ModIfacePhase).
ModIface_ phase -> Maybe HsDocString
mi_doc_hdr = Maybe HsDocString
mb_doc_hdr
, mi_decl_docs :: forall (phase :: ModIfacePhase). ModIface_ phase -> DeclDocMap
mi_decl_docs = DeclDocMap Map Name HsDocString
dmap
, mi_arg_docs :: forall (phase :: ModIfacePhase). ModIface_ phase -> ArgDocMap
mi_arg_docs = ArgDocMap Map Name (Map Int HsDocString)
amap
} <- IO (ModIface_ 'ModIfaceFinal) -> m (ModIface_ 'ModIfaceFinal)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (ModIface_ 'ModIfaceFinal) -> m (ModIface_ 'ModIfaceFinal))
-> IO (ModIface_ 'ModIfaceFinal) -> m (ModIface_ 'ModIfaceFinal)
forall a b. (a -> b) -> a -> b
$ HscEnv -> Module -> IO (ModIface_ 'ModIfaceFinal)
hscGetModuleInterface HscEnv
hsc_env Module
mod
if Maybe HsDocString -> Bool
forall a. Maybe a -> Bool
isNothing Maybe HsDocString
mb_doc_hdr Bool -> Bool -> Bool
&& Map Name HsDocString -> Bool
forall k a. Map k a -> Bool
Map.null Map Name HsDocString
dmap Bool -> Bool -> Bool
&& Map Name (Map Int HsDocString) -> Bool
forall k a. Map k a -> Bool
Map.null Map Name (Map Int HsDocString)
amap
then Either GetDocsFailure (Maybe HsDocString, Map Int HsDocString)
-> m (Either
GetDocsFailure (Maybe HsDocString, Map Int HsDocString))
forall (f :: * -> *) a. Applicative f => a -> f a
pure (GetDocsFailure
-> Either GetDocsFailure (Maybe HsDocString, Map Int HsDocString)
forall a b. a -> Either a b
Left (Module -> Bool -> GetDocsFailure
NoDocsInIface Module
mod Bool
compiled))
else Either GetDocsFailure (Maybe HsDocString, Map Int HsDocString)
-> m (Either
GetDocsFailure (Maybe HsDocString, Map Int HsDocString))
forall (f :: * -> *) a. Applicative f => a -> f a
pure ((Maybe HsDocString, Map Int HsDocString)
-> Either GetDocsFailure (Maybe HsDocString, Map Int HsDocString)
forall a b. b -> Either a b
Right ( Name -> Map Name HsDocString -> Maybe HsDocString
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup Name
name Map Name HsDocString
dmap
, Map Int HsDocString
-> Name -> Map Name (Map Int HsDocString) -> Map Int HsDocString
forall k a. Ord k => a -> k -> Map k a -> a
Map.findWithDefault Map Int HsDocString
forall k a. Map k a
Map.empty Name
name Map Name (Map Int HsDocString)
amap))
where
compiled :: Bool
compiled =
case Name -> SrcLoc
nameSrcLoc Name
name of
RealSrcLoc {} -> Bool
False
UnhelpfulLoc {} -> Bool
True
data GetDocsFailure
= NameHasNoModule Name
| NoDocsInIface
Module
Bool
| InteractiveName
instance Outputable GetDocsFailure where
ppr :: GetDocsFailure -> MsgDoc
ppr (NameHasNoModule Name
name) =
MsgDoc -> MsgDoc
quotes (Name -> MsgDoc
forall a. Outputable a => a -> MsgDoc
ppr Name
name) MsgDoc -> MsgDoc -> MsgDoc
<+> String -> MsgDoc
text String
"has no module where we could look for docs."
ppr (NoDocsInIface Module
mod Bool
compiled) = [MsgDoc] -> MsgDoc
vcat
[ String -> MsgDoc
text String
"Can't find any documentation for" MsgDoc -> MsgDoc -> MsgDoc
<+> Module -> MsgDoc
forall a. Outputable a => a -> MsgDoc
ppr Module
mod MsgDoc -> MsgDoc -> MsgDoc
<> Char -> MsgDoc
char Char
'.'
, String -> MsgDoc
text String
"This is probably because the module was"
MsgDoc -> MsgDoc -> MsgDoc
<+> String -> MsgDoc
text (if Bool
compiled then String
"compiled" else String
"loaded")
MsgDoc -> MsgDoc -> MsgDoc
<+> String -> MsgDoc
text String
"without '-haddock',"
, String -> MsgDoc
text String
"but it's also possible that the module contains no documentation."
, String -> MsgDoc
text String
""
, if Bool
compiled
then String -> MsgDoc
text String
"Try re-compiling with '-haddock'."
else String -> MsgDoc
text String
"Try running ':set -haddock' and :load the file again."
]
ppr GetDocsFailure
InteractiveName =
String -> MsgDoc
text String
"Docs are unavailable for interactive declarations."
exprType :: GhcMonad m => TcRnExprMode -> String -> m Type
exprType :: forall (m :: * -> *).
GhcMonad m =>
TcRnExprMode -> String -> m Kind
exprType TcRnExprMode
mode String
expr = (HscEnv -> m Kind) -> m Kind
forall (m :: * -> *) a. GhcMonad m => (HscEnv -> m a) -> m a
withSession ((HscEnv -> m Kind) -> m Kind) -> (HscEnv -> m Kind) -> m Kind
forall a b. (a -> b) -> a -> b
$ \HscEnv
hsc_env -> do
Kind
ty <- IO Kind -> m Kind
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Kind -> m Kind) -> IO Kind -> m Kind
forall a b. (a -> b) -> a -> b
$ HscEnv -> TcRnExprMode -> String -> IO Kind
hscTcExpr HscEnv
hsc_env TcRnExprMode
mode String
expr
Kind -> m Kind
forall (m :: * -> *) a. Monad m => a -> m a
return (Kind -> m Kind) -> Kind -> m Kind
forall a b. (a -> b) -> a -> b
$ TidyEnv -> Kind -> Kind
tidyType TidyEnv
emptyTidyEnv Kind
ty
typeKind :: GhcMonad m => Bool -> String -> m (Type, Kind)
typeKind :: forall (m :: * -> *).
GhcMonad m =>
Bool -> String -> m (Kind, Kind)
typeKind Bool
normalise String
str = (HscEnv -> m (Kind, Kind)) -> m (Kind, Kind)
forall (m :: * -> *) a. GhcMonad m => (HscEnv -> m a) -> m a
withSession ((HscEnv -> m (Kind, Kind)) -> m (Kind, Kind))
-> (HscEnv -> m (Kind, Kind)) -> m (Kind, Kind)
forall a b. (a -> b) -> a -> b
$ \HscEnv
hsc_env -> do
IO (Kind, Kind) -> m (Kind, Kind)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Kind, Kind) -> m (Kind, Kind))
-> IO (Kind, Kind) -> m (Kind, Kind)
forall a b. (a -> b) -> a -> b
$ HscEnv -> Bool -> String -> IO (Kind, Kind)
hscKcType HscEnv
hsc_env Bool
normalise String
str
getInstancesForType :: GhcMonad m => Type -> m [ClsInst]
getInstancesForType :: forall (m :: * -> *). GhcMonad m => Kind -> m [ClsInst]
getInstancesForType Kind
ty = (HscEnv -> m [ClsInst]) -> m [ClsInst]
forall (m :: * -> *) a. GhcMonad m => (HscEnv -> m a) -> m a
withSession ((HscEnv -> m [ClsInst]) -> m [ClsInst])
-> (HscEnv -> m [ClsInst]) -> m [ClsInst]
forall a b. (a -> b) -> a -> b
$ \HscEnv
hsc_env -> do
IO [ClsInst] -> m [ClsInst]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [ClsInst] -> m [ClsInst]) -> IO [ClsInst] -> m [ClsInst]
forall a b. (a -> b) -> a -> b
$ HscEnv -> Hsc [ClsInst] -> IO [ClsInst]
forall a. HscEnv -> Hsc a -> IO a
runInteractiveHsc HscEnv
hsc_env (Hsc [ClsInst] -> IO [ClsInst]) -> Hsc [ClsInst] -> IO [ClsInst]
forall a b. (a -> b) -> a -> b
$ do
IO (Messages, Maybe [ClsInst]) -> Hsc [ClsInst]
forall a. IO (Messages, Maybe a) -> Hsc a
ioMsgMaybe (IO (Messages, Maybe [ClsInst]) -> Hsc [ClsInst])
-> IO (Messages, Maybe [ClsInst]) -> Hsc [ClsInst]
forall a b. (a -> b) -> a -> b
$ HscEnv -> TcRn [ClsInst] -> IO (Messages, Maybe [ClsInst])
forall a. HscEnv -> TcRn a -> IO (Messages, Maybe a)
runTcInteractive HscEnv
hsc_env (TcRn [ClsInst] -> IO (Messages, Maybe [ClsInst]))
-> TcRn [ClsInst] -> IO (Messages, Maybe [ClsInst])
forall a b. (a -> b) -> a -> b
$ do
HscEnv -> InteractiveContext -> TcM ()
loadUnqualIfaces HscEnv
hsc_env (HscEnv -> InteractiveContext
hsc_IC HscEnv
hsc_env)
[(ClsInst, [Maybe Kind])]
matches <- Kind -> TcM [(ClsInst, [Maybe Kind])]
findMatchingInstances Kind
ty
([Maybe ClsInst] -> [ClsInst])
-> IOEnv (Env TcGblEnv TcLclEnv) [Maybe ClsInst] -> TcRn [ClsInst]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [Maybe ClsInst] -> [ClsInst]
forall a. [Maybe a] -> [a]
catMaybes (IOEnv (Env TcGblEnv TcLclEnv) [Maybe ClsInst] -> TcRn [ClsInst])
-> (((ClsInst, [Maybe Kind])
-> IOEnv (Env TcGblEnv TcLclEnv) (Maybe ClsInst))
-> IOEnv (Env TcGblEnv TcLclEnv) [Maybe ClsInst])
-> ((ClsInst, [Maybe Kind])
-> IOEnv (Env TcGblEnv TcLclEnv) (Maybe ClsInst))
-> TcRn [ClsInst]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [(ClsInst, [Maybe Kind])]
-> ((ClsInst, [Maybe Kind])
-> IOEnv (Env TcGblEnv TcLclEnv) (Maybe ClsInst))
-> IOEnv (Env TcGblEnv TcLclEnv) [Maybe ClsInst]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
t a -> (a -> m b) -> m (t b)
forM [(ClsInst, [Maybe Kind])]
matches (((ClsInst, [Maybe Kind])
-> IOEnv (Env TcGblEnv TcLclEnv) (Maybe ClsInst))
-> TcRn [ClsInst])
-> ((ClsInst, [Maybe Kind])
-> IOEnv (Env TcGblEnv TcLclEnv) (Maybe ClsInst))
-> TcRn [ClsInst]
forall a b. (a -> b) -> a -> b
$ (ClsInst
-> [Maybe Kind] -> IOEnv (Env TcGblEnv TcLclEnv) (Maybe ClsInst))
-> (ClsInst, [Maybe Kind])
-> IOEnv (Env TcGblEnv TcLclEnv) (Maybe ClsInst)
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry ClsInst
-> [Maybe Kind] -> IOEnv (Env TcGblEnv TcLclEnv) (Maybe ClsInst)
checkForExistence
parseInstanceHead :: GhcMonad m => String -> m Type
parseInstanceHead :: forall (m :: * -> *). GhcMonad m => String -> m Kind
parseInstanceHead String
str = (HscEnv -> m Kind) -> m Kind
forall (m :: * -> *) a. GhcMonad m => (HscEnv -> m a) -> m a
withSession ((HscEnv -> m Kind) -> m Kind) -> (HscEnv -> m Kind) -> m Kind
forall a b. (a -> b) -> a -> b
$ \HscEnv
hsc_env0 -> do
(Kind
ty, Kind
_) <- IO (Kind, Kind) -> m (Kind, Kind)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Kind, Kind) -> m (Kind, Kind))
-> IO (Kind, Kind) -> m (Kind, Kind)
forall a b. (a -> b) -> a -> b
$ HscEnv -> Hsc (Kind, Kind) -> IO (Kind, Kind)
forall a. HscEnv -> Hsc a -> IO a
runInteractiveHsc HscEnv
hsc_env0 (Hsc (Kind, Kind) -> IO (Kind, Kind))
-> Hsc (Kind, Kind) -> IO (Kind, Kind)
forall a b. (a -> b) -> a -> b
$ do
HscEnv
hsc_env <- Hsc HscEnv
getHscEnv
LHsType GhcPs
ty <- String -> Hsc (LHsType GhcPs)
hscParseType String
str
IO (Messages, Maybe (Kind, Kind)) -> Hsc (Kind, Kind)
forall a. IO (Messages, Maybe a) -> Hsc a
ioMsgMaybe (IO (Messages, Maybe (Kind, Kind)) -> Hsc (Kind, Kind))
-> IO (Messages, Maybe (Kind, Kind)) -> Hsc (Kind, Kind)
forall a b. (a -> b) -> a -> b
$ HscEnv
-> ZonkFlexi
-> Bool
-> LHsType GhcPs
-> IO (Messages, Maybe (Kind, Kind))
tcRnType HscEnv
hsc_env ZonkFlexi
SkolemiseFlexi Bool
True LHsType GhcPs
ty
Kind -> m Kind
forall (m :: * -> *) a. Monad m => a -> m a
return Kind
ty
getDictionaryBindings :: PredType -> TcM CtEvidence
getDictionaryBindings :: Kind -> TcM CtEvidence
getDictionaryBindings Kind
theta = do
Name
dictName <- OccName -> TcM Name
newName (OccName -> OccName
mkDictOcc (String -> OccName
mkVarOcc String
"magic"))
let dict_var :: Id
dict_var = Name -> Kind -> Id
mkVanillaGlobal Name
dictName Kind
theta
CtLoc
loc <- CtOrigin -> Maybe TypeOrKind -> TcM CtLoc
getCtLocM (SkolemInfo -> CtOrigin
GivenOrigin SkolemInfo
UnkSkol) Maybe TypeOrKind
forall a. Maybe a
Nothing
CtEvidence -> TcM CtEvidence
forall (m :: * -> *) a. Monad m => a -> m a
return CtWanted :: Kind -> TcEvDest -> ShadowInfo -> CtLoc -> CtEvidence
CtWanted {
ctev_pred :: Kind
ctev_pred = Id -> Kind
varType Id
dict_var,
ctev_dest :: TcEvDest
ctev_dest = Id -> TcEvDest
EvVarDest Id
dict_var,
ctev_nosh :: ShadowInfo
ctev_nosh = ShadowInfo
WDeriv,
ctev_loc :: CtLoc
ctev_loc = CtLoc
loc
}
findMatchingInstances :: Type -> TcM [(ClsInst, [DFunInstType])]
findMatchingInstances :: Kind -> TcM [(ClsInst, [Maybe Kind])]
findMatchingInstances Kind
ty = do
ies :: InstEnvs
ies@(InstEnvs {ie_global :: InstEnvs -> InstEnv
ie_global = InstEnv
ie_global, ie_local :: InstEnvs -> InstEnv
ie_local = InstEnv
ie_local}) <- TcM InstEnvs
tcGetInstEnvs
let allClasses :: [Class]
allClasses = InstEnv -> [Class]
instEnvClasses InstEnv
ie_global [Class] -> [Class] -> [Class]
forall a. [a] -> [a] -> [a]
++ InstEnv -> [Class]
instEnvClasses InstEnv
ie_local
[(ClsInst, [Maybe Kind])] -> TcM [(ClsInst, [Maybe Kind])]
forall (m :: * -> *) a. Monad m => a -> m a
return ([(ClsInst, [Maybe Kind])] -> TcM [(ClsInst, [Maybe Kind])])
-> [(ClsInst, [Maybe Kind])] -> TcM [(ClsInst, [Maybe Kind])]
forall a b. (a -> b) -> a -> b
$ (Class -> [(ClsInst, [Maybe Kind])])
-> [Class] -> [(ClsInst, [Maybe Kind])]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (InstEnvs -> Class -> [(ClsInst, [Maybe Kind])]
try_cls InstEnvs
ies) [Class]
allClasses
where
try_cls :: InstEnvs -> Class -> [(ClsInst, [Maybe Kind])]
try_cls InstEnvs
ies Class
cls
| Just (Kind
_, Kind
arg_kind, Kind
res_kind) <- Kind -> Maybe (Kind, Kind, Kind)
splitFunTy_maybe (TyCon -> Kind
tyConKind (TyCon -> Kind) -> TyCon -> Kind
forall a b. (a -> b) -> a -> b
$ Class -> TyCon
classTyCon Class
cls)
, Kind -> Bool
tcIsConstraintKind Kind
res_kind
, HasDebugCallStack => Kind -> Kind
Kind -> Kind
Type.typeKind Kind
ty Kind -> Kind -> Bool
`eqType` Kind
arg_kind
, ([(ClsInst, [Maybe Kind])]
matches, [ClsInst]
_, [(ClsInst, [Maybe Kind])]
_) <- Bool
-> InstEnvs
-> Class
-> [Kind]
-> ([(ClsInst, [Maybe Kind])], [ClsInst],
[(ClsInst, [Maybe Kind])])
lookupInstEnv Bool
True InstEnvs
ies Class
cls [Kind
ty]
= [(ClsInst, [Maybe Kind])]
matches
| Bool
otherwise
= []
checkForExistence :: ClsInst -> [DFunInstType] -> TcM (Maybe ClsInst)
checkForExistence :: ClsInst
-> [Maybe Kind] -> IOEnv (Env TcGblEnv TcLclEnv) (Maybe ClsInst)
checkForExistence ClsInst
clsInst [Maybe Kind]
mb_inst_tys = do
([Kind]
tys, [Kind]
thetas) <- Id -> [Maybe Kind] -> TcM ([Kind], [Kind])
instDFunType (ClsInst -> Id
is_dfun ClsInst
clsInst) [Maybe Kind]
mb_inst_tys
[CtEvidence]
wanteds <- (Kind -> TcM CtEvidence)
-> [Kind] -> IOEnv (Env TcGblEnv TcLclEnv) [CtEvidence]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Kind -> TcM CtEvidence
getDictionaryBindings [Kind]
thetas
WC { wc_simple :: WantedConstraints -> Cts
wc_simple = Cts
simples, wc_impl :: WantedConstraints -> Bag Implication
wc_impl = Bag Implication
impls } <- [CtEvidence] -> TcM WantedConstraints
simplifyWantedsTcM [CtEvidence]
wanteds
if (Ct -> Bool) -> Cts -> Bool
forall a. (a -> Bool) -> Bag a -> Bool
allBag Ct -> Bool
allowedSimple Cts
simples Bool -> Bool -> Bool
&& Bag Implication -> Bool
solvedImplics Bag Implication
impls
then Maybe ClsInst -> IOEnv (Env TcGblEnv TcLclEnv) (Maybe ClsInst)
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe ClsInst -> IOEnv (Env TcGblEnv TcLclEnv) (Maybe ClsInst))
-> (ClsInst -> Maybe ClsInst)
-> ClsInst
-> IOEnv (Env TcGblEnv TcLclEnv) (Maybe ClsInst)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ClsInst -> Maybe ClsInst
forall a. a -> Maybe a
Just (ClsInst -> IOEnv (Env TcGblEnv TcLclEnv) (Maybe ClsInst))
-> ClsInst -> IOEnv (Env TcGblEnv TcLclEnv) (Maybe ClsInst)
forall a b. (a -> b) -> a -> b
$ [Kind] -> [Kind] -> ClsInst -> ClsInst
substInstArgs [Kind]
tys (Bag Kind -> [Kind]
forall a. Bag a -> [a]
bagToList ((Ct -> Kind) -> Cts -> Bag Kind
forall a b. (a -> b) -> Bag a -> Bag b
mapBag Ct -> Kind
ctPred Cts
simples)) ClsInst
clsInst
else Maybe ClsInst -> IOEnv (Env TcGblEnv TcLclEnv) (Maybe ClsInst)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe ClsInst
forall a. Maybe a
Nothing
where
allowedSimple :: Ct -> Bool
allowedSimple :: Ct -> Bool
allowedSimple Ct
ct = Kind -> Bool
isSatisfiablePred (Ct -> Kind
ctPred Ct
ct)
solvedImplics :: Bag Implication -> Bool
solvedImplics :: Bag Implication -> Bool
solvedImplics Bag Implication
impls = (Implication -> Bool) -> Bag Implication -> Bool
forall a. (a -> Bool) -> Bag a -> Bool
allBag (ImplicStatus -> Bool
isSolvedStatus (ImplicStatus -> Bool)
-> (Implication -> ImplicStatus) -> Implication -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Implication -> ImplicStatus
ic_status) Bag Implication
impls
isSatisfiablePred :: PredType -> Bool
isSatisfiablePred :: Kind -> Bool
isSatisfiablePred Kind
ty = case Kind -> Maybe (Class, [Kind])
getClassPredTys_maybe Kind
ty of
Just (Class
_, tys :: [Kind]
tys@(Kind
_:[Kind]
_)) -> (Kind -> Bool) -> [Kind] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all Kind -> Bool
isTyVarTy [Kind]
tys
Maybe (Class, [Kind])
_ -> Kind -> Bool
isTyVarTy Kind
ty
empty_subst :: TCvSubst
empty_subst = InScopeSet -> TCvSubst
mkEmptyTCvSubst (VarSet -> InScopeSet
mkInScopeSet (Kind -> VarSet
tyCoVarsOfType (Id -> Kind
idType (Id -> Kind) -> Id -> Kind
forall a b. (a -> b) -> a -> b
$ ClsInst -> Id
is_dfun ClsInst
clsInst)))
substInstArgs :: [Type] -> [PredType] -> ClsInst -> ClsInst
substInstArgs :: [Kind] -> [Kind] -> ClsInst -> ClsInst
substInstArgs [Kind]
tys [Kind]
thetas ClsInst
inst = let
subst :: TCvSubst
subst = (TCvSubst -> (Id, Kind) -> TCvSubst)
-> TCvSubst -> [(Id, Kind)] -> TCvSubst
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' (\TCvSubst
a (Id, Kind)
b -> (Id -> Kind -> TCvSubst) -> (Id, Kind) -> TCvSubst
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry (TCvSubst -> Id -> Kind -> TCvSubst
extendTvSubstAndInScope TCvSubst
a) (Id, Kind)
b) TCvSubst
empty_subst ([Id] -> [Kind] -> [(Id, Kind)]
forall a b. [a] -> [b] -> [(a, b)]
zip [Id]
dfun_tvs [Kind]
tys)
tau :: Kind
tau = Class -> [Kind] -> Kind
mkClassPred Class
cls (HasCallStack => TCvSubst -> [Kind] -> [Kind]
TCvSubst -> [Kind] -> [Kind]
substTheta TCvSubst
subst [Kind]
args)
phi :: Kind
phi = [Kind] -> Kind -> Kind
mkPhiTy [Kind]
thetas Kind
tau
sigma :: Kind
sigma = [TyCoVarBinder] -> Kind -> Kind
mkForAllTys ((Id -> TyCoVarBinder) -> [Id] -> [TyCoVarBinder]
forall a b. (a -> b) -> [a] -> [b]
map (\Id
v -> Id -> ArgFlag -> TyCoVarBinder
forall var argf. var -> argf -> VarBndr var argf
Bndr Id
v ArgFlag
Inferred) [Id]
dfun_tvs) Kind
phi
in ClsInst
inst { is_dfun :: Id
is_dfun = (ClsInst -> Id
is_dfun ClsInst
inst) { varType :: Kind
varType = Kind
sigma }}
where
([Id]
dfun_tvs, [Kind]
_, Class
cls, [Kind]
args) = ClsInst -> ([Id], [Kind], Class, [Kind])
instanceSig ClsInst
inst
parseExpr :: GhcMonad m => String -> m (LHsExpr GhcPs)
parseExpr :: forall (m :: * -> *). GhcMonad m => String -> m (LHsExpr GhcPs)
parseExpr String
expr = (HscEnv -> m (LHsExpr GhcPs)) -> m (LHsExpr GhcPs)
forall (m :: * -> *) a. GhcMonad m => (HscEnv -> m a) -> m a
withSession ((HscEnv -> m (LHsExpr GhcPs)) -> m (LHsExpr GhcPs))
-> (HscEnv -> m (LHsExpr GhcPs)) -> m (LHsExpr GhcPs)
forall a b. (a -> b) -> a -> b
$ \HscEnv
hsc_env -> do
IO (LHsExpr GhcPs) -> m (LHsExpr GhcPs)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (LHsExpr GhcPs) -> m (LHsExpr GhcPs))
-> IO (LHsExpr GhcPs) -> m (LHsExpr GhcPs)
forall a b. (a -> b) -> a -> b
$ HscEnv -> Hsc (LHsExpr GhcPs) -> IO (LHsExpr GhcPs)
forall a. HscEnv -> Hsc a -> IO a
runInteractiveHsc HscEnv
hsc_env (Hsc (LHsExpr GhcPs) -> IO (LHsExpr GhcPs))
-> Hsc (LHsExpr GhcPs) -> IO (LHsExpr GhcPs)
forall a b. (a -> b) -> a -> b
$ String -> Hsc (LHsExpr GhcPs)
hscParseExpr String
expr
compileExpr :: GhcMonad m => String -> m HValue
compileExpr :: forall (m :: * -> *). GhcMonad m => String -> m HValue
compileExpr String
expr = do
LHsExpr GhcPs
parsed_expr <- String -> m (LHsExpr GhcPs)
forall (m :: * -> *). GhcMonad m => String -> m (LHsExpr GhcPs)
parseExpr String
expr
LHsExpr GhcPs -> m HValue
forall (m :: * -> *). GhcMonad m => LHsExpr GhcPs -> m HValue
compileParsedExpr LHsExpr GhcPs
parsed_expr
compileExprRemote :: GhcMonad m => String -> m ForeignHValue
compileExprRemote :: forall (m :: * -> *). GhcMonad m => String -> m ForeignHValue
compileExprRemote String
expr = do
LHsExpr GhcPs
parsed_expr <- String -> m (LHsExpr GhcPs)
forall (m :: * -> *). GhcMonad m => String -> m (LHsExpr GhcPs)
parseExpr String
expr
LHsExpr GhcPs -> m ForeignHValue
forall (m :: * -> *).
GhcMonad m =>
LHsExpr GhcPs -> m ForeignHValue
compileParsedExprRemote LHsExpr GhcPs
parsed_expr
compileParsedExprRemote :: GhcMonad m => LHsExpr GhcPs -> m ForeignHValue
compileParsedExprRemote :: forall (m :: * -> *).
GhcMonad m =>
LHsExpr GhcPs -> m ForeignHValue
compileParsedExprRemote expr :: LHsExpr GhcPs
expr@(L SrcSpan
loc HsExpr GhcPs
_) = (HscEnv -> m ForeignHValue) -> m ForeignHValue
forall (m :: * -> *) a. GhcMonad m => (HscEnv -> m a) -> m a
withSession ((HscEnv -> m ForeignHValue) -> m ForeignHValue)
-> (HscEnv -> m ForeignHValue) -> m ForeignHValue
forall a b. (a -> b) -> a -> b
$ \HscEnv
hsc_env -> do
let expr_fs :: FastString
expr_fs = String -> FastString
fsLit String
"_compileParsedExpr"
expr_name :: Name
expr_name = Unique -> OccName -> SrcSpan -> Name
mkInternalName (FastString -> Unique
forall a. Uniquable a => a -> Unique
getUnique FastString
expr_fs) (FastString -> OccName
mkTyVarOccFS FastString
expr_fs) SrcSpan
loc
let_stmt :: GenLocated SrcSpan (StmtLR GhcPs GhcPs body)
let_stmt = SrcSpan
-> StmtLR GhcPs GhcPs body
-> GenLocated SrcSpan (StmtLR GhcPs GhcPs body)
forall l e. l -> e -> GenLocated l e
L SrcSpan
loc (StmtLR GhcPs GhcPs body
-> GenLocated SrcSpan (StmtLR GhcPs GhcPs body))
-> (HsValBindsLR GhcPs GhcPs -> StmtLR GhcPs GhcPs body)
-> HsValBindsLR GhcPs GhcPs
-> GenLocated SrcSpan (StmtLR GhcPs GhcPs body)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XLetStmt GhcPs GhcPs body
-> LHsLocalBindsLR GhcPs GhcPs -> StmtLR GhcPs GhcPs body
forall idL idR body.
XLetStmt idL idR body
-> LHsLocalBindsLR idL idR -> StmtLR idL idR body
LetStmt NoExtField
XLetStmt GhcPs GhcPs body
noExtField (LHsLocalBindsLR GhcPs GhcPs -> StmtLR GhcPs GhcPs body)
-> (HsValBindsLR GhcPs GhcPs -> LHsLocalBindsLR GhcPs GhcPs)
-> HsValBindsLR GhcPs GhcPs
-> StmtLR GhcPs GhcPs body
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SrcSpan
-> HsLocalBindsLR GhcPs GhcPs -> LHsLocalBindsLR GhcPs GhcPs
forall l e. l -> e -> GenLocated l e
L SrcSpan
loc (HsLocalBindsLR GhcPs GhcPs -> LHsLocalBindsLR GhcPs GhcPs)
-> (HsValBindsLR GhcPs GhcPs -> HsLocalBindsLR GhcPs GhcPs)
-> HsValBindsLR GhcPs GhcPs
-> LHsLocalBindsLR GhcPs GhcPs
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (XHsValBinds GhcPs GhcPs
-> HsValBindsLR GhcPs GhcPs -> HsLocalBindsLR GhcPs GhcPs
forall idL idR.
XHsValBinds idL idR
-> HsValBindsLR idL idR -> HsLocalBindsLR idL idR
HsValBinds NoExtField
XHsValBinds GhcPs GhcPs
noExtField) (HsValBindsLR GhcPs GhcPs
-> GenLocated SrcSpan (StmtLR GhcPs GhcPs body))
-> HsValBindsLR GhcPs GhcPs
-> GenLocated SrcSpan (StmtLR GhcPs GhcPs body)
forall a b. (a -> b) -> a -> b
$
XValBinds GhcPs GhcPs
-> LHsBindsLR GhcPs GhcPs
-> [LSig GhcPs]
-> HsValBindsLR GhcPs GhcPs
forall idL idR.
XValBinds idL idR
-> LHsBindsLR idL idR -> [LSig idR] -> HsValBindsLR idL idR
ValBinds NoExtField
XValBinds GhcPs GhcPs
noExtField
(LHsBind GhcPs -> LHsBindsLR GhcPs GhcPs
forall a. a -> Bag a
unitBag (LHsBind GhcPs -> LHsBindsLR GhcPs GhcPs)
-> LHsBind GhcPs -> LHsBindsLR GhcPs GhcPs
forall a b. (a -> b) -> a -> b
$ SrcSpan -> RdrName -> LHsExpr GhcPs -> LHsBind GhcPs
mkHsVarBind SrcSpan
loc (Name -> RdrName
forall thing. NamedThing thing => thing -> RdrName
getRdrName Name
expr_name) LHsExpr GhcPs
expr) []
Maybe ([Id], ForeignHValue, FixityEnv)
pstmt <- IO (Maybe ([Id], ForeignHValue, FixityEnv))
-> m (Maybe ([Id], ForeignHValue, FixityEnv))
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe ([Id], ForeignHValue, FixityEnv))
-> m (Maybe ([Id], ForeignHValue, FixityEnv)))
-> IO (Maybe ([Id], ForeignHValue, FixityEnv))
-> m (Maybe ([Id], ForeignHValue, FixityEnv))
forall a b. (a -> b) -> a -> b
$ HscEnv
-> GhciLStmt GhcPs -> IO (Maybe ([Id], ForeignHValue, FixityEnv))
hscParsedStmt HscEnv
hsc_env GhciLStmt GhcPs
forall {body}. GenLocated SrcSpan (StmtLR GhcPs GhcPs body)
let_stmt
let (ForeignHValue
hvals_io, FixityEnv
fix_env) = case Maybe ([Id], ForeignHValue, FixityEnv)
pstmt of
Just ([Id
_id], ForeignHValue
hvals_io', FixityEnv
fix_env') -> (ForeignHValue
hvals_io', FixityEnv
fix_env')
Maybe ([Id], ForeignHValue, FixityEnv)
_ -> String -> (ForeignHValue, FixityEnv)
forall a. String -> a
panic String
"compileParsedExprRemote"
FixityEnv -> m ()
forall (m :: * -> *). GhcMonad m => FixityEnv -> m ()
updateFixityEnv FixityEnv
fix_env
EvalStatus_ [ForeignHValue] [HValueRef]
status <- IO (EvalStatus_ [ForeignHValue] [HValueRef])
-> m (EvalStatus_ [ForeignHValue] [HValueRef])
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (EvalStatus_ [ForeignHValue] [HValueRef])
-> m (EvalStatus_ [ForeignHValue] [HValueRef]))
-> IO (EvalStatus_ [ForeignHValue] [HValueRef])
-> m (EvalStatus_ [ForeignHValue] [HValueRef])
forall a b. (a -> b) -> a -> b
$ HscEnv
-> Bool
-> EvalExpr ForeignHValue
-> IO (EvalStatus_ [ForeignHValue] [HValueRef])
evalStmt HscEnv
hsc_env Bool
False (ForeignHValue -> EvalExpr ForeignHValue
forall a. a -> EvalExpr a
EvalThis ForeignHValue
hvals_io)
case EvalStatus_ [ForeignHValue] [HValueRef]
status of
EvalComplete Word64
_ (EvalSuccess [ForeignHValue
hval]) -> ForeignHValue -> m ForeignHValue
forall (m :: * -> *) a. Monad m => a -> m a
return ForeignHValue
hval
EvalComplete Word64
_ (EvalException SerializableException
e) ->
IO ForeignHValue -> m ForeignHValue
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ForeignHValue -> m ForeignHValue)
-> IO ForeignHValue -> m ForeignHValue
forall a b. (a -> b) -> a -> b
$ SomeException -> IO ForeignHValue
forall e a. Exception e => e -> IO a
throwIO (SerializableException -> SomeException
fromSerializableException SerializableException
e)
EvalStatus_ [ForeignHValue] [HValueRef]
_ -> String -> m ForeignHValue
forall a. String -> a
panic String
"compileParsedExpr"
compileParsedExpr :: GhcMonad m => LHsExpr GhcPs -> m HValue
compileParsedExpr :: forall (m :: * -> *). GhcMonad m => LHsExpr GhcPs -> m HValue
compileParsedExpr LHsExpr GhcPs
expr = do
ForeignHValue
fhv <- LHsExpr GhcPs -> m ForeignHValue
forall (m :: * -> *).
GhcMonad m =>
LHsExpr GhcPs -> m ForeignHValue
compileParsedExprRemote LHsExpr GhcPs
expr
HscEnv
hsc_env <- m HscEnv
forall (m :: * -> *). GhcMonad m => m HscEnv
getSession
IO HValue -> m HValue
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO HValue -> m HValue) -> IO HValue -> m HValue
forall a b. (a -> b) -> a -> b
$ HscEnv -> (Interp -> IO HValue) -> IO HValue
forall a. HscEnv -> (Interp -> IO a) -> IO a
withInterp HscEnv
hsc_env ((Interp -> IO HValue) -> IO HValue)
-> (Interp -> IO HValue) -> IO HValue
forall a b. (a -> b) -> a -> b
$ \Interp
interp ->
Interp -> ForeignHValue -> IO HValue
forall a. Interp -> ForeignRef a -> IO a
wormhole Interp
interp ForeignHValue
fhv
dynCompileExpr :: GhcMonad m => String -> m Dynamic
dynCompileExpr :: forall (m :: * -> *). GhcMonad m => String -> m Dynamic
dynCompileExpr String
expr = do
LHsExpr GhcPs
parsed_expr <- String -> m (LHsExpr GhcPs)
forall (m :: * -> *). GhcMonad m => String -> m (LHsExpr GhcPs)
parseExpr String
expr
let loc :: SrcSpan
loc = LHsExpr GhcPs -> SrcSpan
forall l e. GenLocated l e -> l
getLoc LHsExpr GhcPs
parsed_expr
to_dyn_expr :: LHsExpr GhcPs
to_dyn_expr = LHsExpr GhcPs -> LHsExpr GhcPs -> LHsExpr GhcPs
forall (id :: Pass).
LHsExpr (GhcPass id)
-> LHsExpr (GhcPass id) -> LHsExpr (GhcPass id)
mkHsApp (SrcSpan -> HsExpr GhcPs -> LHsExpr GhcPs
forall l e. l -> e -> GenLocated l e
L SrcSpan
loc (HsExpr GhcPs -> LHsExpr GhcPs)
-> (RdrName -> HsExpr GhcPs) -> RdrName -> LHsExpr GhcPs
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XVar GhcPs -> Located (IdP GhcPs) -> HsExpr GhcPs
forall p. XVar p -> Located (IdP p) -> HsExpr p
HsVar NoExtField
XVar GhcPs
noExtField (Located RdrName -> HsExpr GhcPs)
-> (RdrName -> Located RdrName) -> RdrName -> HsExpr GhcPs
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SrcSpan -> RdrName -> Located RdrName
forall l e. l -> e -> GenLocated l e
L SrcSpan
loc (RdrName -> LHsExpr GhcPs) -> RdrName -> LHsExpr GhcPs
forall a b. (a -> b) -> a -> b
$ Name -> RdrName
forall thing. NamedThing thing => thing -> RdrName
getRdrName Name
toDynName)
LHsExpr GhcPs
parsed_expr
HValue
hval <- LHsExpr GhcPs -> m HValue
forall (m :: * -> *). GhcMonad m => LHsExpr GhcPs -> m HValue
compileParsedExpr LHsExpr GhcPs
to_dyn_expr
Dynamic -> m Dynamic
forall (m :: * -> *) a. Monad m => a -> m a
return (HValue -> Dynamic
forall a b. a -> b
unsafeCoerce HValue
hval :: Dynamic)
showModule :: GhcMonad m => ModSummary -> m String
showModule :: forall (m :: * -> *). GhcMonad m => ModSummary -> m String
showModule ModSummary
mod_summary =
(HscEnv -> m String) -> m String
forall (m :: * -> *) a. GhcMonad m => (HscEnv -> m a) -> m a
withSession ((HscEnv -> m String) -> m String)
-> (HscEnv -> m String) -> m String
forall a b. (a -> b) -> a -> b
$ \HscEnv
hsc_env -> do
Bool
interpreted <- ModSummary -> m Bool
forall (m :: * -> *). GhcMonad m => ModSummary -> m Bool
moduleIsBootOrNotObjectLinkable ModSummary
mod_summary
let dflags :: DynFlags
dflags = HscEnv -> DynFlags
hsc_dflags HscEnv
hsc_env
String -> m String
forall (m :: * -> *) a. Monad m => a -> m a
return (DynFlags -> HscTarget -> Bool -> ModSummary -> String
showModMsg DynFlags
dflags (DynFlags -> HscTarget
hscTarget DynFlags
dflags) Bool
interpreted ModSummary
mod_summary)
moduleIsBootOrNotObjectLinkable :: GhcMonad m => ModSummary -> m Bool
moduleIsBootOrNotObjectLinkable :: forall (m :: * -> *). GhcMonad m => ModSummary -> m Bool
moduleIsBootOrNotObjectLinkable ModSummary
mod_summary = (HscEnv -> m Bool) -> m Bool
forall (m :: * -> *) a. GhcMonad m => (HscEnv -> m a) -> m a
withSession ((HscEnv -> m Bool) -> m Bool) -> (HscEnv -> m Bool) -> m Bool
forall a b. (a -> b) -> a -> b
$ \HscEnv
hsc_env ->
case HomePackageTable -> ModuleName -> Maybe HomeModInfo
lookupHpt (HscEnv -> HomePackageTable
hsc_HPT HscEnv
hsc_env) (ModSummary -> ModuleName
ms_mod_name ModSummary
mod_summary) of
Maybe HomeModInfo
Nothing -> String -> m Bool
forall a. String -> a
panic String
"missing linkable"
Just HomeModInfo
mod_info -> Bool -> m Bool
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool -> m Bool) -> Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ case HomeModInfo -> Maybe Linkable
hm_linkable HomeModInfo
mod_info of
Maybe Linkable
Nothing -> Bool
True
Just Linkable
linkable -> Bool -> Bool
not (Linkable -> Bool
isObjectLinkable Linkable
linkable)
obtainTermFromVal :: HscEnv -> Int -> Bool -> Type -> a -> IO Term
#if defined(HAVE_INTERNAL_INTERPRETER)
obtainTermFromVal :: forall a. HscEnv -> Int -> Bool -> Kind -> a -> IO Term
obtainTermFromVal HscEnv
hsc_env Int
bound Bool
force Kind
ty a
x = HscEnv -> (Interp -> IO Term) -> IO Term
forall a. HscEnv -> (Interp -> IO a) -> IO a
withInterp HscEnv
hsc_env ((Interp -> IO Term) -> IO Term) -> (Interp -> IO Term) -> IO Term
forall a b. (a -> b) -> a -> b
$ \case
Interp
InternalInterp -> HscEnv -> Int -> Bool -> Kind -> ForeignHValue -> IO Term
cvObtainTerm HscEnv
hsc_env Int
bound Bool
force Kind
ty (a -> ForeignHValue
forall a b. a -> b
unsafeCoerce a
x)
#else
obtainTermFromVal hsc_env _bound _force _ty _x = withInterp hsc_env $ \case
#endif
ExternalInterp {} -> GhcException -> IO Term
forall e a. Exception e => e -> IO a
throwIO (String -> GhcException
InstallationError
String
"this operation requires -fno-external-interpreter")
obtainTermFromId :: HscEnv -> Int -> Bool -> Id -> IO Term
obtainTermFromId :: HscEnv -> Int -> Bool -> Id -> IO Term
obtainTermFromId HscEnv
hsc_env Int
bound Bool
force Id
id = do
ForeignHValue
hv <- HscEnv -> Name -> IO ForeignHValue
Linker.getHValue HscEnv
hsc_env (Id -> Name
varName Id
id)
HscEnv -> Int -> Bool -> Kind -> ForeignHValue -> IO Term
cvObtainTerm (HscEnv -> HscEnv
updEnv HscEnv
hsc_env) Int
bound Bool
force (Id -> Kind
idType Id
id) ForeignHValue
hv
where updEnv :: HscEnv -> HscEnv
updEnv HscEnv
env = HscEnv
env {hsc_dflags :: DynFlags
hsc_dflags =
DynFlags -> Extension -> DynFlags
xopt_set (HscEnv -> DynFlags
hsc_dflags HscEnv
env) Extension
ImpredicativeTypes}
reconstructType :: HscEnv -> Int -> Id -> IO (Maybe Type)
reconstructType :: HscEnv -> Int -> Id -> IO (Maybe Kind)
reconstructType HscEnv
hsc_env Int
bound Id
id = do
ForeignHValue
hv <- HscEnv -> Name -> IO ForeignHValue
Linker.getHValue HscEnv
hsc_env (Id -> Name
varName Id
id)
HscEnv -> Int -> Kind -> ForeignHValue -> IO (Maybe Kind)
cvReconstructType HscEnv
hsc_env Int
bound (Id -> Kind
idType Id
id) ForeignHValue
hv
mkRuntimeUnkTyVar :: Name -> Kind -> TyVar
mkRuntimeUnkTyVar :: Name -> Kind -> Id
mkRuntimeUnkTyVar Name
name Kind
kind = Name -> Kind -> TcTyVarDetails -> Id
mkTcTyVar Name
name Kind
kind TcTyVarDetails
RuntimeUnk