{-# LANGUAGE CPP #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE ExtendedDefaultRules #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE NoMonomorphismRestriction #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE ViewPatterns #-}
{-# OPTIONS_GHC -fno-warn-type-defaults #-}
module Ide.Plugin.Eval.CodeLens (
codeLens,
evalCommand,
) where
import Control.Applicative (Alternative ((<|>)))
import Control.Arrow (second, (>>>))
import Control.Exception (try)
import qualified Control.Exception as E
import Control.Lens (_1, _3, ix, (%~), (<&>), (^.))
import Control.Monad (guard, join, void, when)
import Control.Monad.IO.Class (MonadIO (liftIO))
import Control.Monad.Trans (lift)
import Control.Monad.Trans.Except (ExceptT (..))
import Data.Aeson (toJSON)
import Data.Char (isSpace)
import Data.Default
import qualified Data.HashMap.Strict as HashMap
import Data.List (dropWhileEnd, find,
intercalate, intersperse)
import Data.Maybe (catMaybes, fromMaybe)
import Data.String (IsString)
import Data.Text (Text)
import qualified Data.Text as T
import Data.Time (getCurrentTime)
import Data.Typeable (Typeable)
import Development.IDE (GetModSummary (..),
GhcSessionIO (..), IdeState,
ModSummaryResult (..),
NeedsCompilation (NeedsCompilation),
evalGhcEnv,
hscEnvWithImportPaths,
printOutputable, runAction,
textToStringBuffer,
toNormalizedFilePath',
uriToFilePath', useNoFile_,
useWithStale_, use_,
VFSModified(..))
import Development.IDE.Core.Rules (GhcSessionDepsConfig (..),
ghcSessionDepsDefinition)
import Development.IDE.GHC.Compat hiding (typeKind, unitState)
import qualified Development.IDE.GHC.Compat as Compat
import qualified Development.IDE.GHC.Compat as SrcLoc
import Development.IDE.GHC.Compat.Util (GhcException,
OverridingBool (..))
import Development.IDE.Types.Options
import GHC (ClsInst,
ExecOptions (execLineNumber, execSourceFile),
FamInst, GhcMonad,
LoadHowMuch (LoadAllTargets),
NamedThing (getName),
defaultFixity, execOptions,
exprType, getInfo,
getInteractiveDynFlags,
isImport, isStmt, load,
parseName, pprFamInst,
pprInstance, setTargets,
typeKind)
#if MIN_VERSION_ghc(9,2,0)
import GHC (Fixity)
#endif
import qualified GHC.LanguageExtensions.Type as LangExt (Extension (..))
import Development.IDE.Core.FileStore (setSomethingModified)
import Development.IDE.Types.Shake (toKey)
import Ide.Plugin.Config (Config)
#if MIN_VERSION_ghc(9,2,0)
import GHC.Types.SrcLoc (UnhelpfulSpanReason (UnhelpfulInteractive))
#endif
import Ide.Plugin.Eval.Code (Statement, asStatements,
evalSetup, myExecStmt,
propSetup, resultRange,
testCheck, testRanges)
import Ide.Plugin.Eval.Config (getEvalConfig, EvalConfig(..))
import Ide.Plugin.Eval.GHC (addImport, addPackages,
hasPackage, showDynFlags)
import Ide.Plugin.Eval.Parse.Comments (commentsToSections)
import Ide.Plugin.Eval.Parse.Option (parseSetFlags)
import Ide.Plugin.Eval.Rules (queueForEvaluation)
import Ide.Plugin.Eval.Types
import Ide.Plugin.Eval.Util (gStrictTry, isLiterate,
logWith, response', timed)
import Ide.PluginUtils (handleMaybe, handleMaybeM,
response)
import Ide.Types
import Language.LSP.Server
import Language.LSP.Types hiding
(SemanticTokenAbsolute (length, line),
SemanticTokenRelative (length))
import Language.LSP.Types.Lens (end, line)
import Language.LSP.VFS (virtualFileText)
#if MIN_VERSION_ghc(9,2,0)
#elif MIN_VERSION_ghc(9,0,0)
import GHC.Driver.Session (unitDatabases, unitState)
import GHC.Types.SrcLoc (UnhelpfulSpanReason (UnhelpfulInteractive))
#else
import DynFlags
#endif
codeLens :: PluginMethodHandler IdeState TextDocumentCodeLens
codeLens :: PluginMethodHandler IdeState 'TextDocumentCodeLens
codeLens IdeState
st PluginId
plId CodeLensParams{_textDocument} =
let dbg :: a1 -> a2 -> m ()
dbg = IdeState -> a1 -> a2 -> m ()
forall (m :: * -> *) a1 a2.
(HasCallStack, MonadIO m, Show a1, Show a2) =>
IdeState -> a1 -> a2 -> m ()
logWith IdeState
st
perf :: a1 -> m b -> m b
perf = (a1 -> String -> m ()) -> a1 -> m b -> m b
forall (m :: * -> *) t a b.
MonadIO m =>
(t -> String -> m a) -> t -> m b -> m b
timed a1 -> String -> m ()
forall (m :: * -> *) a1 a2.
(MonadIO m, Show a1, Show a2) =>
a1 -> a2 -> m ()
dbg
in String
-> LspT Config IO (Either ResponseError (List CodeLens))
-> LspT Config IO (Either ResponseError (List CodeLens))
forall (m :: * -> *) a1 b. (MonadIO m, Show a1) => a1 -> m b -> m b
perf String
"codeLens" (LspT Config IO (Either ResponseError (List CodeLens))
-> LspT Config IO (Either ResponseError (List CodeLens)))
-> LspT Config IO (Either ResponseError (List CodeLens))
-> LspT Config IO (Either ResponseError (List CodeLens))
forall a b. (a -> b) -> a -> b
$
ExceptT String (LspT Config IO) (List CodeLens)
-> LspT Config IO (Either ResponseError (List CodeLens))
forall (m :: * -> *) a.
Monad m =>
ExceptT String m a -> m (Either ResponseError a)
response (ExceptT String (LspT Config IO) (List CodeLens)
-> LspT Config IO (Either ResponseError (List CodeLens)))
-> ExceptT String (LspT Config IO) (List CodeLens)
-> LspT Config IO (Either ResponseError (List CodeLens))
forall a b. (a -> b) -> a -> b
$ do
let TextDocumentIdentifier Uri
uri = TextDocumentIdentifier
_textDocument
String
fp <- String -> Maybe String -> ExceptT String (LspT Config IO) String
forall (m :: * -> *) e b. Monad m => e -> Maybe b -> ExceptT e m b
handleMaybe String
"uri" (Maybe String -> ExceptT String (LspT Config IO) String)
-> Maybe String -> ExceptT String (LspT Config IO) String
forall a b. (a -> b) -> a -> b
$ Uri -> Maybe String
uriToFilePath' Uri
uri
let nfp :: NormalizedFilePath
nfp = String -> NormalizedFilePath
toNormalizedFilePath' String
fp
isLHS :: Bool
isLHS = String -> Bool
isLiterate String
fp
String -> String -> ExceptT String (LspT Config IO) ()
forall (m :: * -> *) a1 a2.
(MonadIO m, Show a1, Show a2) =>
a1 -> a2 -> m ()
dbg String
"fp" String
fp
(Comments
comments, PositionMapping
_) <- IO (Comments, PositionMapping)
-> ExceptT String (LspT Config IO) (Comments, PositionMapping)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Comments, PositionMapping)
-> ExceptT String (LspT Config IO) (Comments, PositionMapping))
-> IO (Comments, PositionMapping)
-> ExceptT String (LspT Config IO) (Comments, PositionMapping)
forall a b. (a -> b) -> a -> b
$
String
-> IdeState
-> Action (Comments, PositionMapping)
-> IO (Comments, PositionMapping)
forall a. String -> IdeState -> Action a -> IO a
runAction String
"eval.GetParsedModuleWithComments" IdeState
st (Action (Comments, PositionMapping)
-> IO (Comments, PositionMapping))
-> Action (Comments, PositionMapping)
-> IO (Comments, PositionMapping)
forall a b. (a -> b) -> a -> b
$ GetEvalComments
-> NormalizedFilePath -> Action (Comments, PositionMapping)
forall k v.
IdeRule k v =>
k -> NormalizedFilePath -> Action (v, PositionMapping)
useWithStale_ GetEvalComments
GetEvalComments NormalizedFilePath
nfp
String -> String -> ExceptT String (LspT Config IO) ()
forall (m :: * -> *) a1 a2.
(MonadIO m, Show a1, Show a2) =>
a1 -> a2 -> m ()
dbg String
"comments" (String -> ExceptT String (LspT Config IO) ())
-> String -> ExceptT String (LspT Config IO) ()
forall a b. (a -> b) -> a -> b
$ Comments -> String
forall a. Show a => a -> String
show Comments
comments
let Sections{[Section]
setupSections :: Sections -> [Section]
nonSetupSections :: Sections -> [Section]
setupSections :: [Section]
nonSetupSections :: [Section]
..} = Bool -> Comments -> Sections
commentsToSections Bool
isLHS Comments
comments
tests :: [(Section, EvalId, Test)]
tests = [Section] -> [(Section, EvalId, Test)]
testsBySection [Section]
nonSetupSections
cmd :: Command
cmd = PluginId -> CommandId -> Text -> Maybe [Value] -> Command
mkLspCommand PluginId
plId CommandId
evalCommandName Text
"Evaluate=..." ([Value] -> Maybe [Value]
forall a. a -> Maybe a
Just [])
let lenses :: [CodeLens]
lenses =
[ Range -> Maybe Command -> Maybe Value -> CodeLens
CodeLens Range
testRange (Command -> Maybe Command
forall a. a -> Maybe a
Just Command
cmd') Maybe Value
forall a. Maybe a
Nothing
| (Section
section, EvalId
ident, Test
test) <- [(Section, EvalId, Test)]
tests
, let (Range
testRange, Range
resultRange) = Test -> (Range, Range)
testRanges Test
test
args :: EvalParams
args = [Section] -> TextDocumentIdentifier -> EvalId -> EvalParams
EvalParams ([Section]
setupSections [Section] -> [Section] -> [Section]
forall a. [a] -> [a] -> [a]
++ [Section
section]) TextDocumentIdentifier
_textDocument EvalId
ident
cmd' :: Command
cmd' =
(Command
cmd :: Command)
{ $sel:_arguments:Command :: Maybe (List Value)
_arguments = List Value -> Maybe (List Value)
forall a. a -> Maybe a
Just ([Value] -> List Value
forall a. [a] -> List a
List [EvalParams -> Value
forall a. ToJSON a => a -> Value
toJSON EvalParams
args])
, $sel:_title:Command :: Text
_title =
if Range -> Bool
trivial Range
resultRange
then Text
"Evaluate..."
else Text
"Refresh..."
}
]
String
-> ExceptT String (LspT Config IO) ()
-> ExceptT String (LspT Config IO) ()
forall (m :: * -> *) a1 b. (MonadIO m, Show a1) => a1 -> m b -> m b
perf String
"tests" (ExceptT String (LspT Config IO) ()
-> ExceptT String (LspT Config IO) ())
-> ExceptT String (LspT Config IO) ()
-> ExceptT String (LspT Config IO) ()
forall a b. (a -> b) -> a -> b
$
String -> String -> ExceptT String (LspT Config IO) ()
forall (m :: * -> *) a1 a2.
(MonadIO m, Show a1, Show a2) =>
a1 -> a2 -> m ()
dbg String
"Tests" (String -> ExceptT String (LspT Config IO) ())
-> String -> ExceptT String (LspT Config IO) ()
forall a b. (a -> b) -> a -> b
$
[String] -> String
unwords
[ EvalId -> String
forall a. Show a => a -> String
show ([(Section, EvalId, Test)] -> EvalId
forall (t :: * -> *) a. Foldable t => t a -> EvalId
length [(Section, EvalId, Test)]
tests)
, String
"tests in"
, EvalId -> String
forall a. Show a => a -> String
show ([Section] -> EvalId
forall (t :: * -> *) a. Foldable t => t a -> EvalId
length [Section]
nonSetupSections)
, String
"sections"
, EvalId -> String
forall a. Show a => a -> String
show ([Section] -> EvalId
forall (t :: * -> *) a. Foldable t => t a -> EvalId
length [Section]
setupSections)
, String
"setups"
, EvalId -> String
forall a. Show a => a -> String
show ([CodeLens] -> EvalId
forall (t :: * -> *) a. Foldable t => t a -> EvalId
length [CodeLens]
lenses)
, String
"lenses."
]
List CodeLens -> ExceptT String (LspT Config IO) (List CodeLens)
forall (m :: * -> *) a. Monad m => a -> m a
return (List CodeLens -> ExceptT String (LspT Config IO) (List CodeLens))
-> List CodeLens -> ExceptT String (LspT Config IO) (List CodeLens)
forall a b. (a -> b) -> a -> b
$ [CodeLens] -> List CodeLens
forall a. [a] -> List a
List [CodeLens]
lenses
where
trivial :: Range -> Bool
trivial (Range Position
p Position
p') = Position
p Position -> Position -> Bool
forall a. Eq a => a -> a -> Bool
== Position
p'
evalCommandName :: CommandId
evalCommandName :: CommandId
evalCommandName = CommandId
"evalCommand"
evalCommand :: PluginId -> PluginCommand IdeState
evalCommand :: PluginId -> PluginCommand IdeState
evalCommand PluginId
plId = CommandId
-> Text
-> CommandFunction IdeState EvalParams
-> PluginCommand IdeState
forall ideState a.
FromJSON a =>
CommandId
-> Text -> CommandFunction ideState a -> PluginCommand ideState
PluginCommand CommandId
evalCommandName Text
"evaluate" (PluginId -> CommandFunction IdeState EvalParams
runEvalCmd PluginId
plId)
type EvalId = Int
runEvalCmd :: PluginId -> CommandFunction IdeState EvalParams
runEvalCmd :: PluginId -> CommandFunction IdeState EvalParams
runEvalCmd PluginId
plId IdeState
st EvalParams{EvalId
[Section]
TextDocumentIdentifier
evalId :: EvalParams -> EvalId
module_ :: EvalParams -> TextDocumentIdentifier
sections :: EvalParams -> [Section]
evalId :: EvalId
module_ :: TextDocumentIdentifier
sections :: [Section]
..} =
let dbg :: a1 -> a2 -> m ()
dbg = IdeState -> a1 -> a2 -> m ()
forall (m :: * -> *) a1 a2.
(HasCallStack, MonadIO m, Show a1, Show a2) =>
IdeState -> a1 -> a2 -> m ()
logWith IdeState
st
perf :: a1 -> m b -> m b
perf = (a1 -> String -> m ()) -> a1 -> m b -> m b
forall (m :: * -> *) t a b.
MonadIO m =>
(t -> String -> m a) -> t -> m b -> m b
timed a1 -> String -> m ()
forall (m :: * -> *) a1 a2.
(MonadIO m, Show a1, Show a2) =>
a1 -> a2 -> m ()
dbg
cmd :: ExceptT String (LspM Config) WorkspaceEdit
cmd :: ExceptT String (LspT Config IO) WorkspaceEdit
cmd = do
let tests :: [(Section, Test)]
tests = ((Section, EvalId, Test) -> (Section, Test))
-> [(Section, EvalId, Test)] -> [(Section, Test)]
forall a b. (a -> b) -> [a] -> [b]
map (\(Section
a,EvalId
_,Test
b) -> (Section
a,Test
b)) ([(Section, EvalId, Test)] -> [(Section, Test)])
-> [(Section, EvalId, Test)] -> [(Section, Test)]
forall a b. (a -> b) -> a -> b
$ [Section] -> [(Section, EvalId, Test)]
testsBySection [Section]
sections
let TextDocumentIdentifier{Uri
$sel:_uri:TextDocumentIdentifier :: TextDocumentIdentifier -> Uri
_uri :: Uri
_uri} = TextDocumentIdentifier
module_
String
fp <- String -> Maybe String -> ExceptT String (LspT Config IO) String
forall (m :: * -> *) e b. Monad m => e -> Maybe b -> ExceptT e m b
handleMaybe String
"uri" (Maybe String -> ExceptT String (LspT Config IO) String)
-> Maybe String -> ExceptT String (LspT Config IO) String
forall a b. (a -> b) -> a -> b
$ Uri -> Maybe String
uriToFilePath' Uri
_uri
let nfp :: NormalizedFilePath
nfp = String -> NormalizedFilePath
toNormalizedFilePath' String
fp
Text
mdlText <- Uri -> ExceptT String (LspT Config IO) Text
forall e c (m :: * -> *).
(IsString e, MonadLsp c m) =>
Uri -> ExceptT e m Text
moduleText Uri
_uri
IO () -> ExceptT String (LspT Config IO) ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> ExceptT String (LspT Config IO) ())
-> IO () -> ExceptT String (LspT Config IO) ()
forall a b. (a -> b) -> a -> b
$ IdeState -> NormalizedFilePath -> IO ()
queueForEvaluation IdeState
st NormalizedFilePath
nfp
IO () -> ExceptT String (LspT Config IO) ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> ExceptT String (LspT Config IO) ())
-> IO () -> ExceptT String (LspT Config IO) ()
forall a b. (a -> b) -> a -> b
$ VFSModified -> IdeState -> [Key] -> String -> IO ()
setSomethingModified VFSModified
VFSUnmodified IdeState
st [NeedsCompilation -> NormalizedFilePath -> Key
forall k. ShakeValue k => k -> NormalizedFilePath -> Key
toKey NeedsCompilation
NeedsCompilation NormalizedFilePath
nfp] String
"Eval"
HscEnv
session <- IdeState
-> NormalizedFilePath -> ExceptT String (LspT Config IO) HscEnv
forall (m :: * -> *).
MonadIO m =>
IdeState -> NormalizedFilePath -> m HscEnv
runGetSession IdeState
st NormalizedFilePath
nfp
ModSummary
ms <- (ModSummaryResult -> ModSummary)
-> ExceptT String (LspT Config IO) ModSummaryResult
-> ExceptT String (LspT Config IO) ModSummary
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ModSummaryResult -> ModSummary
msrModSummary (ExceptT String (LspT Config IO) ModSummaryResult
-> ExceptT String (LspT Config IO) ModSummary)
-> ExceptT String (LspT Config IO) ModSummaryResult
-> ExceptT String (LspT Config IO) ModSummary
forall a b. (a -> b) -> a -> b
$
IO ModSummaryResult
-> ExceptT String (LspT Config IO) ModSummaryResult
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ModSummaryResult
-> ExceptT String (LspT Config IO) ModSummaryResult)
-> IO ModSummaryResult
-> ExceptT String (LspT Config IO) ModSummaryResult
forall a b. (a -> b) -> a -> b
$
String
-> IdeState -> Action ModSummaryResult -> IO ModSummaryResult
forall a. String -> IdeState -> Action a -> IO a
runAction String
"runEvalCmd.getModSummary" IdeState
st (Action ModSummaryResult -> IO ModSummaryResult)
-> Action ModSummaryResult -> IO ModSummaryResult
forall a b. (a -> b) -> a -> b
$
GetModSummary -> NormalizedFilePath -> Action ModSummaryResult
forall k v. IdeRule k v => k -> NormalizedFilePath -> Action v
use_ GetModSummary
GetModSummary NormalizedFilePath
nfp
UTCTime
now <- IO UTCTime -> ExceptT String (LspT Config IO) UTCTime
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO IO UTCTime
getCurrentTime
let modName :: ModuleName
modName = Module -> ModuleName
moduleName (Module -> ModuleName) -> Module -> ModuleName
forall a b. (a -> b) -> a -> b
$ ModSummary -> Module
ms_mod ModSummary
ms
thisModuleTarget :: Target
thisModuleTarget =
TargetId -> Bool -> Maybe (InputFileBuffer, UTCTime) -> Target
Target
(String -> Maybe Phase -> TargetId
TargetFile String
fp Maybe Phase
forall a. Maybe a
Nothing)
Bool
False
((InputFileBuffer, UTCTime) -> Maybe (InputFileBuffer, UTCTime)
forall a. a -> Maybe a
Just (Text -> InputFileBuffer
textToStringBuffer Text
mdlText, UTCTime
now))
HscEnv
hscEnv' <- LspM Config (Either String HscEnv)
-> ExceptT String (LspT Config IO) HscEnv
forall e (m :: * -> *) a. m (Either e a) -> ExceptT e m a
ExceptT (LspM Config (Either String HscEnv)
-> ExceptT String (LspT Config IO) HscEnv)
-> LspM Config (Either String HscEnv)
-> ExceptT String (LspT Config IO) HscEnv
forall a b. (a -> b) -> a -> b
$ (Either String (Either String HscEnv) -> Either String HscEnv)
-> LspM Config (Either String (Either String HscEnv))
-> LspM Config (Either String HscEnv)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Either String (Either String HscEnv) -> Either String HscEnv
forall (m :: * -> *) a. Monad m => m (m a) -> m a
join (LspM Config (Either String (Either String HscEnv))
-> LspM Config (Either String HscEnv))
-> LspM Config (Either String (Either String HscEnv))
-> LspM Config (Either String HscEnv)
forall a b. (a -> b) -> a -> b
$ IO (Either String (Either String HscEnv))
-> LspM Config (Either String (Either String HscEnv))
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Either String (Either String HscEnv))
-> LspM Config (Either String (Either String HscEnv)))
-> (Ghc (Either String HscEnv)
-> IO (Either String (Either String HscEnv)))
-> Ghc (Either String HscEnv)
-> LspM Config (Either String (Either String HscEnv))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IO (Either String HscEnv)
-> IO (Either String (Either String HscEnv))
forall (m :: * -> *) b.
(MonadIO m, MonadCatch m) =>
m b -> m (Either String b)
gStrictTry (IO (Either String HscEnv)
-> IO (Either String (Either String HscEnv)))
-> (Ghc (Either String HscEnv) -> IO (Either String HscEnv))
-> Ghc (Either String HscEnv)
-> IO (Either String (Either String HscEnv))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HscEnv -> Ghc (Either String HscEnv) -> IO (Either String HscEnv)
forall b. HscEnv -> Ghc b -> IO b
evalGhcEnv HscEnv
session (Ghc (Either String HscEnv)
-> LspM Config (Either String (Either String HscEnv)))
-> Ghc (Either String HscEnv)
-> LspM Config (Either String (Either String HscEnv))
forall a b. (a -> b) -> a -> b
$ do
HscEnv
env <- Ghc HscEnv
forall (m :: * -> *). GhcMonad m => m HscEnv
getSession
DynFlags
df <- IO DynFlags -> Ghc DynFlags
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO DynFlags -> Ghc DynFlags) -> IO DynFlags -> Ghc DynFlags
forall a b. (a -> b) -> a -> b
$ HscEnv -> DynFlags -> IO DynFlags
setupDynFlagsForGHCiLike HscEnv
env (DynFlags -> IO DynFlags) -> DynFlags -> IO DynFlags
forall a b. (a -> b) -> a -> b
$ ModSummary -> DynFlags
ms_hspp_opts ModSummary
ms
let impPaths :: [String]
impPaths = DynFlags -> [String]
importPaths (DynFlags -> [String]) -> DynFlags -> [String]
forall a b. (a -> b) -> a -> b
$ HscEnv -> DynFlags
hsc_dflags HscEnv
env
DynFlags
df <- DynFlags -> Ghc DynFlags
forall (m :: * -> *) a. Monad m => a -> m a
return DynFlags
df{importPaths :: [String]
importPaths = [String]
impPaths}
[InstalledUnitId]
_lp <- DynFlags -> Ghc [InstalledUnitId]
forall (m :: * -> *). GhcMonad m => DynFlags -> m [InstalledUnitId]
setSessionDynFlags DynFlags
df
Bool -> Ghc () -> Ghc ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when ([(Section, Test)] -> Bool
needsQuickCheck [(Section, Test)]
tests) (Ghc () -> Ghc ()) -> Ghc () -> Ghc ()
forall a b. (a -> b) -> a -> b
$ Ghc (Either String DynFlags) -> Ghc ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (Ghc (Either String DynFlags) -> Ghc ())
-> Ghc (Either String DynFlags) -> Ghc ()
forall a b. (a -> b) -> a -> b
$ [String] -> Ghc (Either String DynFlags)
addPackages [String
"QuickCheck"]
String -> Bool -> Ghc ()
forall (m :: * -> *) a1 a2.
(MonadIO m, Show a1, Show a2) =>
a1 -> a2 -> m ()
dbg String
"QUICKCHECK NEEDS" (Bool -> Ghc ()) -> Bool -> Ghc ()
forall a b. (a -> b) -> a -> b
$ [(Section, Test)] -> Bool
needsQuickCheck [(Section, Test)]
tests
String -> Bool -> Ghc ()
forall (m :: * -> *) a1 a2.
(MonadIO m, Show a1, Show a2) =>
a1 -> a2 -> m ()
dbg String
"QUICKCHECK HAS" (Bool -> Ghc ()) -> Bool -> Ghc ()
forall a b. (a -> b) -> a -> b
$ DynFlags -> Bool
hasQuickCheck DynFlags
df
DynFlags
idflags <- Ghc DynFlags
forall (m :: * -> *). GhcMonad m => m DynFlags
getInteractiveDynFlags
DynFlags
df <- Ghc DynFlags
forall (m :: * -> *). GhcMonad m => m DynFlags
getSessionDynFlags
let df' :: DynFlags
df' = (DynFlags -> Extension -> DynFlags)
-> Extension -> DynFlags -> DynFlags
forall a b c. (a -> b -> c) -> b -> a -> c
flip DynFlags -> Extension -> DynFlags
xopt_set Extension
LangExt.ExtendedDefaultRules
(DynFlags -> DynFlags)
-> (DynFlags -> DynFlags) -> DynFlags -> DynFlags
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (DynFlags -> Extension -> DynFlags)
-> Extension -> DynFlags -> DynFlags
forall a b c. (a -> b -> c) -> b -> a -> c
flip DynFlags -> Extension -> DynFlags
xopt_unset Extension
LangExt.MonomorphismRestriction
(DynFlags -> DynFlags) -> DynFlags -> DynFlags
forall a b. (a -> b) -> a -> b
$ DynFlags
idflags
DynFlags -> Ghc ()
forall (m :: * -> *). GhcMonad m => DynFlags -> m ()
setInteractiveDynFlags (DynFlags -> Ghc ()) -> DynFlags -> Ghc ()
forall a b. (a -> b) -> a -> b
$ DynFlags
df'
#if MIN_VERSION_ghc(9,0,0)
{
packageFlags =
packageFlags
df
, useColor = Never
, canUseColor = False
}
#else
{ pkgState :: PackageState
pkgState =
DynFlags -> PackageState
pkgState
DynFlags
df
, pkgDatabase :: Maybe [(String, [PackageConfig])]
pkgDatabase =
DynFlags -> Maybe [(String, [PackageConfig])]
pkgDatabase
DynFlags
df
, packageFlags :: [PackageFlag]
packageFlags =
DynFlags -> [PackageFlag]
packageFlags
DynFlags
df
, useColor :: OverridingBool
useColor = OverridingBool
Never
, canUseColor :: Bool
canUseColor = Bool
False
}
#endif
Either String ()
eSetTarget <- Ghc () -> Ghc (Either String ())
forall (m :: * -> *) b.
(MonadIO m, MonadCatch m) =>
m b -> m (Either String b)
gStrictTry (Ghc () -> Ghc (Either String ()))
-> Ghc () -> Ghc (Either String ())
forall a b. (a -> b) -> a -> b
$ [Target] -> Ghc ()
forall (m :: * -> *). GhcMonad m => [Target] -> m ()
setTargets [Target
thisModuleTarget]
String -> Either String () -> Ghc ()
forall (m :: * -> *) a1 a2.
(MonadIO m, Show a1, Show a2) =>
a1 -> a2 -> m ()
dbg String
"setTarget" Either String ()
eSetTarget
SuccessFlag
loadResult <- String -> Ghc SuccessFlag -> Ghc SuccessFlag
forall (m :: * -> *) a1 b. (MonadIO m, Show a1) => a1 -> m b -> m b
perf String
"loadModule" (Ghc SuccessFlag -> Ghc SuccessFlag)
-> Ghc SuccessFlag -> Ghc SuccessFlag
forall a b. (a -> b) -> a -> b
$ LoadHowMuch -> Ghc SuccessFlag
forall (m :: * -> *). GhcMonad m => LoadHowMuch -> m SuccessFlag
load LoadHowMuch
LoadAllTargets
String -> Text -> Ghc ()
forall (m :: * -> *) a1 a2.
(MonadIO m, Show a1, Show a2) =>
a1 -> a2 -> m ()
dbg String
"LOAD RESULT" (Text -> Ghc ()) -> Text -> Ghc ()
forall a b. (a -> b) -> a -> b
$ SuccessFlag -> Text
forall a. Outputable a => a -> Text
printOutputable SuccessFlag
loadResult
case SuccessFlag
loadResult of
SuccessFlag
Failed -> IO (Either String HscEnv) -> Ghc (Either String HscEnv)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Either String HscEnv) -> Ghc (Either String HscEnv))
-> IO (Either String HscEnv) -> Ghc (Either String HscEnv)
forall a b. (a -> b) -> a -> b
$ do
let err :: p
err = p
""
String -> String -> IO ()
forall (m :: * -> *) a1 a2.
(MonadIO m, Show a1, Show a2) =>
a1 -> a2 -> m ()
dbg String
"load ERR" String
forall p. IsString p => p
err
Either String HscEnv -> IO (Either String HscEnv)
forall (m :: * -> *) a. Monad m => a -> m a
return (Either String HscEnv -> IO (Either String HscEnv))
-> Either String HscEnv -> IO (Either String HscEnv)
forall a b. (a -> b) -> a -> b
$ String -> Either String HscEnv
forall a b. a -> Either a b
Left String
forall p. IsString p => p
err
SuccessFlag
Succeeded -> do
[InteractiveImport] -> Ghc ()
forall (m :: * -> *). GhcMonad m => [InteractiveImport] -> m ()
setContext [ModuleName -> InteractiveImport
Compat.IIModule ModuleName
modName]
HscEnv -> Either String HscEnv
forall a b. b -> Either a b
Right (HscEnv -> Either String HscEnv)
-> Ghc HscEnv -> Ghc (Either String HscEnv)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Ghc HscEnv
forall (m :: * -> *). GhcMonad m => m HscEnv
getSession
EvalConfig
evalCfg <- LspM Config EvalConfig
-> ExceptT String (LspT Config IO) EvalConfig
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (LspM Config EvalConfig
-> ExceptT String (LspT Config IO) EvalConfig)
-> LspM Config EvalConfig
-> ExceptT String (LspT Config IO) EvalConfig
forall a b. (a -> b) -> a -> b
$ PluginId -> LspM Config EvalConfig
forall (m :: * -> *). MonadLsp Config m => PluginId -> m EvalConfig
getEvalConfig PluginId
plId
[TextEdit]
edits <-
String
-> ExceptT String (LspT Config IO) [TextEdit]
-> ExceptT String (LspT Config IO) [TextEdit]
forall (m :: * -> *) a1 b. (MonadIO m, Show a1) => a1 -> m b -> m b
perf String
"edits" (ExceptT String (LspT Config IO) [TextEdit]
-> ExceptT String (LspT Config IO) [TextEdit])
-> ExceptT String (LspT Config IO) [TextEdit]
-> ExceptT String (LspT Config IO) [TextEdit]
forall a b. (a -> b) -> a -> b
$
IO [TextEdit] -> ExceptT String (LspT Config IO) [TextEdit]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [TextEdit] -> ExceptT String (LspT Config IO) [TextEdit])
-> IO [TextEdit] -> ExceptT String (LspT Config IO) [TextEdit]
forall a b. (a -> b) -> a -> b
$
HscEnv -> Ghc [TextEdit] -> IO [TextEdit]
forall b. HscEnv -> Ghc b -> IO b
evalGhcEnv HscEnv
hscEnv' (Ghc [TextEdit] -> IO [TextEdit])
-> Ghc [TextEdit] -> IO [TextEdit]
forall a b. (a -> b) -> a -> b
$
EvalConfig -> TEnv -> [(Section, Test)] -> Ghc [TextEdit]
runTests
EvalConfig
evalCfg
(IdeState
st, String
fp)
[(Section, Test)]
tests
let workspaceEditsMap :: HashMap Uri (List TextEdit)
workspaceEditsMap = [(Uri, List TextEdit)] -> HashMap Uri (List TextEdit)
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList [(Uri
_uri, [TextEdit] -> List TextEdit
forall a. [a] -> List a
List ([TextEdit] -> List TextEdit) -> [TextEdit] -> List TextEdit
forall a b. (a -> b) -> a -> b
$ Text -> [TextEdit] -> [TextEdit]
addFinalReturn Text
mdlText [TextEdit]
edits)]
let workspaceEdits :: WorkspaceEdit
workspaceEdits = Maybe (HashMap Uri (List TextEdit))
-> Maybe (List DocumentChange)
-> Maybe ChangeAnnotationMap
-> WorkspaceEdit
WorkspaceEdit (HashMap Uri (List TextEdit) -> Maybe (HashMap Uri (List TextEdit))
forall a. a -> Maybe a
Just HashMap Uri (List TextEdit)
workspaceEditsMap) Maybe (List DocumentChange)
forall a. Maybe a
Nothing Maybe ChangeAnnotationMap
forall a. Maybe a
Nothing
WorkspaceEdit -> ExceptT String (LspT Config IO) WorkspaceEdit
forall (m :: * -> *) a. Monad m => a -> m a
return WorkspaceEdit
workspaceEdits
in String
-> LspT Config IO (Either ResponseError Value)
-> LspT Config IO (Either ResponseError Value)
forall (m :: * -> *) a1 b. (MonadIO m, Show a1) => a1 -> m b -> m b
perf String
"evalCmd" (LspT Config IO (Either ResponseError Value)
-> LspT Config IO (Either ResponseError Value))
-> LspT Config IO (Either ResponseError Value)
-> LspT Config IO (Either ResponseError Value)
forall a b. (a -> b) -> a -> b
$
Text
-> ProgressCancellable
-> LspT Config IO (Either ResponseError Value)
-> LspT Config IO (Either ResponseError Value)
forall c (m :: * -> *) a.
MonadLsp c m =>
Text -> ProgressCancellable -> m a -> m a
withIndefiniteProgress Text
"Evaluating" ProgressCancellable
Cancellable (LspT Config IO (Either ResponseError Value)
-> LspT Config IO (Either ResponseError Value))
-> LspT Config IO (Either ResponseError Value)
-> LspT Config IO (Either ResponseError Value)
forall a b. (a -> b) -> a -> b
$
ExceptT String (LspT Config IO) WorkspaceEdit
-> LspT Config IO (Either ResponseError Value)
forall c.
ExceptT String (LspM c) WorkspaceEdit
-> LspM c (Either ResponseError Value)
response' ExceptT String (LspT Config IO) WorkspaceEdit
cmd
addFinalReturn :: Text -> [TextEdit] -> [TextEdit]
addFinalReturn :: Text -> [TextEdit] -> [TextEdit]
addFinalReturn Text
mdlText [TextEdit]
edits
| Bool -> Bool
not ([TextEdit] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [TextEdit]
edits) Bool -> Bool -> Bool
&& Bool -> Bool
not (Text -> Bool
T.null Text
mdlText) Bool -> Bool -> Bool
&& Text -> Char
T.last Text
mdlText Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/= Char
'\n' =
Text -> TextEdit
finalReturn Text
mdlText TextEdit -> [TextEdit] -> [TextEdit]
forall a. a -> [a] -> [a]
: [TextEdit]
edits
| Bool
otherwise = [TextEdit]
edits
finalReturn :: Text -> TextEdit
finalReturn :: Text -> TextEdit
finalReturn Text
txt =
let ls :: [Text]
ls = Text -> [Text]
T.lines Text
txt
l :: b
l = EvalId -> b
forall a b. (Integral a, Num b) => a -> b
fromIntegral (EvalId -> b) -> EvalId -> b
forall a b. (a -> b) -> a -> b
$ [Text] -> EvalId
forall (t :: * -> *) a. Foldable t => t a -> EvalId
length [Text]
ls EvalId -> EvalId -> EvalId
forall a. Num a => a -> a -> a
-EvalId
1
c :: b
c = EvalId -> b
forall a b. (Integral a, Num b) => a -> b
fromIntegral (EvalId -> b) -> EvalId -> b
forall a b. (a -> b) -> a -> b
$ Text -> EvalId
T.length (Text -> EvalId) -> ([Text] -> Text) -> [Text] -> EvalId
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Text] -> Text
forall a. [a] -> a
last ([Text] -> EvalId) -> [Text] -> EvalId
forall a b. (a -> b) -> a -> b
$ [Text]
ls
p :: Position
p = UInt -> UInt -> Position
Position UInt
forall b. Num b => b
l UInt
forall b. Num b => b
c
in Range -> Text -> TextEdit
TextEdit (Position -> Position -> Range
Range Position
p Position
p) Text
"\n"
moduleText :: (IsString e, MonadLsp c m) => Uri -> ExceptT e m Text
moduleText :: Uri -> ExceptT e m Text
moduleText Uri
uri =
e -> m (Maybe Text) -> ExceptT e m Text
forall (m :: * -> *) e b.
Monad m =>
e -> m (Maybe b) -> ExceptT e m b
handleMaybeM e
"mdlText" (m (Maybe Text) -> ExceptT e m Text)
-> m (Maybe Text) -> ExceptT e m Text
forall a b. (a -> b) -> a -> b
$
(VirtualFile -> Text
virtualFileText (VirtualFile -> Text) -> Maybe VirtualFile -> Maybe Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>)
(Maybe VirtualFile -> Maybe Text)
-> m (Maybe VirtualFile) -> m (Maybe Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> NormalizedUri -> m (Maybe VirtualFile)
forall config (m :: * -> *).
MonadLsp config m =>
NormalizedUri -> m (Maybe VirtualFile)
getVirtualFile
(Uri -> NormalizedUri
toNormalizedUri Uri
uri)
testsBySection :: [Section] -> [(Section, EvalId, Test)]
testsBySection :: [Section] -> [(Section, EvalId, Test)]
testsBySection [Section]
sections =
[(Section
section, EvalId
ident, Test
test)
| (EvalId
ident, Section
section) <- [EvalId] -> [Section] -> [(EvalId, Section)]
forall a b. [a] -> [b] -> [(a, b)]
zip [EvalId
0..] [Section]
sections
, Test
test <- Section -> [Test]
sectionTests Section
section
]
type TEnv = (IdeState, String)
runTests :: EvalConfig -> TEnv -> [(Section, Test)] -> Ghc [TextEdit]
runTests :: EvalConfig -> TEnv -> [(Section, Test)] -> Ghc [TextEdit]
runTests EvalConfig{Bool
eval_cfg_exception :: EvalConfig -> Bool
eval_cfg_diff :: EvalConfig -> Bool
eval_cfg_exception :: Bool
eval_cfg_diff :: Bool
..} e :: TEnv
e@(IdeState
_st, String
_) [(Section, Test)]
tests = do
DynFlags
df <- Ghc DynFlags
forall (m :: * -> *). GhcMonad m => m DynFlags
getInteractiveDynFlags
Ghc ()
evalSetup
Bool -> Ghc () -> Ghc ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (DynFlags -> Bool
hasQuickCheck DynFlags
df Bool -> Bool -> Bool
&& [(Section, Test)] -> Bool
needsQuickCheck [(Section, Test)]
tests) (Ghc () -> Ghc ()) -> Ghc () -> Ghc ()
forall a b. (a -> b) -> a -> b
$ Ghc [Text] -> Ghc ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (Ghc [Text] -> Ghc ()) -> Ghc [Text] -> Ghc ()
forall a b. (a -> b) -> a -> b
$ Bool -> TEnv -> DynFlags -> [Statement] -> Ghc [Text]
evals Bool
True TEnv
e DynFlags
df [Statement]
propSetup
((Section, Test) -> Ghc TextEdit)
-> [(Section, Test)] -> Ghc [TextEdit]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (TEnv -> DynFlags -> (Section, Test) -> Ghc TextEdit
processTest TEnv
e DynFlags
df) [(Section, Test)]
tests
where
processTest :: TEnv -> DynFlags -> (Section, Test) -> Ghc TextEdit
processTest :: TEnv -> DynFlags -> (Section, Test) -> Ghc TextEdit
processTest e :: TEnv
e@(IdeState
st, String
fp) DynFlags
df (Section
section, Test
test) = do
let dbg :: a1 -> a2 -> m ()
dbg = IdeState -> a1 -> a2 -> m ()
forall (m :: * -> *) a1 a2.
(HasCallStack, MonadIO m, Show a1, Show a2) =>
IdeState -> a1 -> a2 -> m ()
logWith IdeState
st
let pad :: Text -> Text
pad = Text -> Text -> Text
pad_ (Text -> Text -> Text) -> Text -> Text -> Text
forall a b. (a -> b) -> a -> b
$ (if String -> Bool
isLiterate String
fp then (Text
"> " Text -> Text -> Text
`T.append`) else Text -> Text
forall a. a -> a
id) (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ Format -> Text
forall p. IsString p => Format -> p
padPrefix (Section -> Format
sectionFormat Section
section)
[Text]
rs <- TEnv -> DynFlags -> Test -> Ghc [Text]
runTest TEnv
e DynFlags
df Test
test
String -> [Text] -> Ghc ()
forall (m :: * -> *) a1 a2.
(MonadIO m, Show a1, Show a2) =>
a1 -> a2 -> m ()
dbg String
"TEST RESULTS" [Text]
rs
let checkedResult :: [Text]
checkedResult = Bool -> (Section, Test) -> [Text] -> [Text]
testCheck Bool
eval_cfg_diff (Section
section, Test
test) [Text]
rs
let edit :: TextEdit
edit = Format -> Test -> [Text] -> TextEdit
asEdit (Section -> Format
sectionFormat Section
section) Test
test ((Text -> Text) -> [Text] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map Text -> Text
pad [Text]
checkedResult)
String -> TextEdit -> Ghc ()
forall (m :: * -> *) a1 a2.
(MonadIO m, Show a1, Show a2) =>
a1 -> a2 -> m ()
dbg String
"TEST EDIT" TextEdit
edit
TextEdit -> Ghc TextEdit
forall (m :: * -> *) a. Monad m => a -> m a
return TextEdit
edit
runTest :: TEnv -> DynFlags -> Test -> Ghc [Text]
runTest TEnv
_ DynFlags
df Test
test
| Bool -> Bool
not (DynFlags -> Bool
hasQuickCheck DynFlags
df) Bool -> Bool -> Bool
&& Test -> Bool
isProperty Test
test =
[Text] -> Ghc [Text]
forall (m :: * -> *) a. Monad m => a -> m a
return ([Text] -> Ghc [Text]) -> [Text] -> Ghc [Text]
forall a b. (a -> b) -> a -> b
$
String -> [Text]
singleLine
String
"Add QuickCheck to your cabal dependencies to run this test."
runTest TEnv
e DynFlags
df Test
test = Bool -> TEnv -> DynFlags -> [Statement] -> Ghc [Text]
evals (Bool
eval_cfg_exception Bool -> Bool -> Bool
&& Bool -> Bool
not (Test -> Bool
isProperty Test
test)) TEnv
e DynFlags
df (Test -> [Statement]
asStatements Test
test)
asEdit :: Format -> Test -> [Text] -> TextEdit
asEdit :: Format -> Test -> [Text] -> TextEdit
asEdit (MultiLine Range
commRange) Test
test [Text]
resultLines
| Test -> Range
testRange Test
test Range -> Getting UInt Range UInt -> UInt
forall s a. s -> Getting a s a -> a
^. (Position -> Const UInt Position) -> Range -> Const UInt Range
forall s a. HasEnd s a => Lens' s a
end((Position -> Const UInt Position) -> Range -> Const UInt Range)
-> ((UInt -> Const UInt UInt) -> Position -> Const UInt Position)
-> Getting UInt Range UInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(UInt -> Const UInt UInt) -> Position -> Const UInt Position
forall s a. HasLine s a => Lens' s a
line UInt -> UInt -> Bool
forall a. Eq a => a -> a -> Bool
== Range
commRange Range -> Getting UInt Range UInt -> UInt
forall s a. s -> Getting a s a -> a
^. (Position -> Const UInt Position) -> Range -> Const UInt Range
forall s a. HasEnd s a => Lens' s a
end ((Position -> Const UInt Position) -> Range -> Const UInt Range)
-> ((UInt -> Const UInt UInt) -> Position -> Const UInt Position)
-> Getting UInt Range UInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (UInt -> Const UInt UInt) -> Position -> Const UInt Position
forall s a. HasLine s a => Lens' s a
line
=
Range -> Text -> TextEdit
TextEdit
(Position -> Position -> Range
Range
(Test -> Range
testRange Test
test Range -> Getting Position Range Position -> Position
forall s a. s -> Getting a s a -> a
^. Getting Position Range Position
forall s a. HasEnd s a => Lens' s a
end)
(Test -> Range
resultRange Test
test Range -> Getting Position Range Position -> Position
forall s a. s -> Getting a s a -> a
^. Getting Position Range Position
forall s a. HasEnd s a => Lens' s a
end)
)
(Text
"\n" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> [Text] -> Text
T.unlines ([Text]
resultLines [Text] -> [Text] -> [Text]
forall a. Semigroup a => a -> a -> a
<> [Text
"-}"]))
asEdit Format
_ Test
test [Text]
resultLines =
Range -> Text -> TextEdit
TextEdit (Test -> Range
resultRange Test
test) ([Text] -> Text
T.unlines [Text]
resultLines)
evals :: Bool -> TEnv -> DynFlags -> [Statement] -> Ghc [Text]
evals :: Bool -> TEnv -> DynFlags -> [Statement] -> Ghc [Text]
evals Bool
mark_exception (IdeState
st, String
fp) DynFlags
df [Statement]
stmts = do
Either String [Maybe [Text]]
er <- Ghc [Maybe [Text]] -> Ghc (Either String [Maybe [Text]])
forall (m :: * -> *) b.
(MonadIO m, MonadCatch m) =>
m b -> m (Either String b)
gStrictTry (Ghc [Maybe [Text]] -> Ghc (Either String [Maybe [Text]]))
-> Ghc [Maybe [Text]] -> Ghc (Either String [Maybe [Text]])
forall a b. (a -> b) -> a -> b
$ (Statement -> Ghc (Maybe [Text]))
-> [Statement] -> Ghc [Maybe [Text]]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Statement -> Ghc (Maybe [Text])
eval [Statement]
stmts
[Text] -> Ghc [Text]
forall (m :: * -> *) a. Monad m => a -> m a
return ([Text] -> Ghc [Text]) -> [Text] -> Ghc [Text]
forall a b. (a -> b) -> a -> b
$ case Either String [Maybe [Text]]
er of
Left String
err -> String -> [Text]
errorLines String
err
Right [Maybe [Text]]
rs -> [[Text]] -> [Text]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([[Text]] -> [Text])
-> ([Maybe [Text]] -> [[Text]]) -> [Maybe [Text]] -> [Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Maybe [Text]] -> [[Text]]
forall a. [Maybe a] -> [a]
catMaybes ([Maybe [Text]] -> [Text]) -> [Maybe [Text]] -> [Text]
forall a b. (a -> b) -> a -> b
$ [Maybe [Text]]
rs
where
dbg :: a1 -> a2 -> m ()
dbg = IdeState -> a1 -> a2 -> m ()
forall (m :: * -> *) a1 a2.
(HasCallStack, MonadIO m, Show a1, Show a2) =>
IdeState -> a1 -> a2 -> m ()
logWith IdeState
st
eval :: Statement -> Ghc (Maybe [Text])
eval :: Statement -> Ghc (Maybe [Text])
eval (Located EvalId
l String
stmt)
|
Just (String -> [String]
words -> [String]
flags) <- String -> Maybe String
parseSetFlags String
stmt = do
String -> [String] -> Ghc ()
forall (m :: * -> *) a1 a2.
(MonadIO m, Show a1, Show a2) =>
a1 -> a2 -> m ()
dbg String
"{:SET" [String]
flags
DynFlags
ndf <- Ghc DynFlags
forall (m :: * -> *). GhcMonad m => m DynFlags
getInteractiveDynFlags
String -> String -> Ghc ()
forall (m :: * -> *) a1 a2.
(MonadIO m, Show a1, Show a2) =>
a1 -> a2 -> m ()
dbg String
"pre set" (String -> Ghc ()) -> String -> Ghc ()
forall a b. (a -> b) -> a -> b
$ DynFlags -> String
showDynFlags DynFlags
ndf
Either GhcException (DynFlags, [Located String], [Warn])
eans <-
IO (Either GhcException (DynFlags, [Located String], [Warn]))
-> Ghc (Either GhcException (DynFlags, [Located String], [Warn]))
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Either GhcException (DynFlags, [Located String], [Warn]))
-> Ghc (Either GhcException (DynFlags, [Located String], [Warn])))
-> IO (Either GhcException (DynFlags, [Located String], [Warn]))
-> Ghc (Either GhcException (DynFlags, [Located String], [Warn]))
forall a b. (a -> b) -> a -> b
$ forall a.
Exception GhcException =>
IO a -> IO (Either GhcException a)
forall e a. Exception e => IO a -> IO (Either e a)
try @GhcException (IO (DynFlags, [Located String], [Warn])
-> IO (Either GhcException (DynFlags, [Located String], [Warn])))
-> IO (DynFlags, [Located String], [Warn])
-> IO (Either GhcException (DynFlags, [Located String], [Warn]))
forall a b. (a -> b) -> a -> b
$
DynFlags
-> [Located String] -> IO (DynFlags, [Located String], [Warn])
forall (m :: * -> *).
MonadIO m =>
DynFlags
-> [Located String] -> m (DynFlags, [Located String], [Warn])
parseDynamicFlagsCmdLine DynFlags
ndf
((String -> Located String) -> [String] -> [Located String]
forall a b. (a -> b) -> [a] -> [b]
map (SrcSpan -> String -> Located String
forall l e. l -> e -> GenLocated l e
L (SrcSpan -> String -> Located String)
-> SrcSpan -> String -> Located String
forall a b. (a -> b) -> a -> b
$ FastString -> SrcSpan
UnhelpfulSpan FastString
forall p. IsString p => p
unhelpfulReason) [String]
flags)
String
-> Either GhcException (String, [Located String], [Located String])
-> Ghc ()
forall (m :: * -> *) a1 a2.
(MonadIO m, Show a1, Show a2) =>
a1 -> a2 -> m ()
dbg String
"parsed flags" (Either GhcException (String, [Located String], [Located String])
-> Ghc ())
-> Either GhcException (String, [Located String], [Located String])
-> Ghc ()
forall a b. (a -> b) -> a -> b
$ Either GhcException (DynFlags, [Located String], [Warn])
eans
Either GhcException (DynFlags, [Located String], [Warn])
-> ((DynFlags, [Located String], [Warn])
-> (String, [Located String], [Located String]))
-> Either GhcException (String, [Located String], [Located String])
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> ((DynFlags -> Identity String)
-> (DynFlags, [Located String], [Warn])
-> Identity (String, [Located String], [Warn])
forall s t a b. Field1 s t a b => Lens s t a b
_1 ((DynFlags -> Identity String)
-> (DynFlags, [Located String], [Warn])
-> Identity (String, [Located String], [Warn]))
-> (DynFlags -> String)
-> (DynFlags, [Located String], [Warn])
-> (String, [Located String], [Warn])
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
%~ DynFlags -> String
showDynFlags ((DynFlags, [Located String], [Warn])
-> (String, [Located String], [Warn]))
-> ((String, [Located String], [Warn])
-> (String, [Located String], [Located String]))
-> (DynFlags, [Located String], [Warn])
-> (String, [Located String], [Located String])
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> ([Warn] -> Identity [Located String])
-> (String, [Located String], [Warn])
-> Identity (String, [Located String], [Located String])
forall s t a b. Field3 s t a b => Lens s t a b
_3 (([Warn] -> Identity [Located String])
-> (String, [Located String], [Warn])
-> Identity (String, [Located String], [Located String]))
-> ([Warn] -> [Located String])
-> (String, [Located String], [Warn])
-> (String, [Located String], [Located String])
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
%~ (Warn -> Located String) -> [Warn] -> [Located String]
forall a b. (a -> b) -> [a] -> [b]
map Warn -> Located String
warnMsg)
case Either GhcException (DynFlags, [Located String], [Warn])
eans of
Left GhcException
err -> Maybe [Text] -> Ghc (Maybe [Text])
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Maybe [Text] -> Ghc (Maybe [Text]))
-> Maybe [Text] -> Ghc (Maybe [Text])
forall a b. (a -> b) -> a -> b
$ [Text] -> Maybe [Text]
forall a. a -> Maybe a
Just ([Text] -> Maybe [Text]) -> [Text] -> Maybe [Text]
forall a b. (a -> b) -> a -> b
$ String -> [Text]
errorLines (String -> [Text]) -> String -> [Text]
forall a b. (a -> b) -> a -> b
$ GhcException -> String
forall a. Show a => a -> String
show GhcException
err
Right (DynFlags
df', [Located String]
ignoreds, [Warn]
warns) -> do
let warnings :: m [Text]
warnings = do
Bool -> m ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> m ()) -> Bool -> m ()
forall a b. (a -> b) -> a -> b
$ Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ [Warn] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Warn]
warns
[Text] -> m [Text]
forall (f :: * -> *) a. Applicative f => a -> f a
pure ([Text] -> m [Text]) -> [Text] -> m [Text]
forall a b. (a -> b) -> a -> b
$ String -> [Text]
errorLines (String -> [Text]) -> String -> [Text]
forall a b. (a -> b) -> a -> b
$
[String] -> String
unlines ([String] -> String) -> [String] -> String
forall a b. (a -> b) -> a -> b
$
(Warn -> String) -> [Warn] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map Warn -> String
prettyWarn [Warn]
warns
igns :: m [Text]
igns = do
Bool -> m ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> m ()) -> Bool -> m ()
forall a b. (a -> b) -> a -> b
$ Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ [Located String] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Located String]
ignoreds
[Text] -> m [Text]
forall (f :: * -> *) a. Applicative f => a -> f a
pure
[Text
"Some flags have not been recognized: "
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> String -> Text
T.pack (String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
intercalate String
", " ([String] -> String) -> [String] -> String
forall a b. (a -> b) -> a -> b
$ (Located String -> String) -> [Located String] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map Located String -> String
forall a. HasSrcSpan a => a -> SrcSpanLess a
SrcLoc.unLoc [Located String]
ignoreds)
]
String -> String -> Ghc ()
forall (m :: * -> *) a1 a2.
(MonadIO m, Show a1, Show a2) =>
a1 -> a2 -> m ()
dbg String
"post set" (String -> Ghc ()) -> String -> Ghc ()
forall a b. (a -> b) -> a -> b
$ DynFlags -> String
showDynFlags DynFlags
df'
[InstalledUnitId]
_ <- DynFlags -> Ghc [InstalledUnitId]
forall (m :: * -> *). GhcMonad m => DynFlags -> m [InstalledUnitId]
setSessionDynFlags DynFlags
df'
DynFlags
sessDyns <- Ghc DynFlags
forall (m :: * -> *). GhcMonad m => m DynFlags
getSessionDynFlags
DynFlags -> Ghc ()
forall (m :: * -> *). GhcMonad m => DynFlags -> m ()
setInteractiveDynFlags DynFlags
sessDyns
Maybe [Text] -> Ghc (Maybe [Text])
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Maybe [Text] -> Ghc (Maybe [Text]))
-> Maybe [Text] -> Ghc (Maybe [Text])
forall a b. (a -> b) -> a -> b
$ Maybe [Text]
forall (m :: * -> *). (Monad m, Alternative m) => m [Text]
warnings Maybe [Text] -> Maybe [Text] -> Maybe [Text]
forall a. Semigroup a => a -> a -> a
<> Maybe [Text]
forall (m :: * -> *). (Monad m, Alternative m) => m [Text]
igns
|
Just (Text
cmd, Text
arg) <- Text -> Maybe (Text, Text)
parseGhciLikeCmd (Text -> Maybe (Text, Text)) -> Text -> Maybe (Text, Text)
forall a b. (a -> b) -> a -> b
$ String -> Text
T.pack String
stmt =
Text -> Text -> Ghc (Maybe [Text])
evalGhciLikeCmd Text
cmd Text
arg
|
DynFlags -> String -> Bool
isStmt DynFlags
pf String
stmt =
do
String -> String -> Ghc ()
forall (m :: * -> *) a1 a2.
(MonadIO m, Show a1, Show a2) =>
a1 -> a2 -> m ()
dbg String
"{STMT " String
stmt
Either String (Maybe String)
res <- String -> EvalId -> Ghc (Either String (Maybe String))
exec String
stmt EvalId
l
let r :: Maybe [Text]
r = case Either String (Maybe String)
res of
Left String
err -> [Text] -> Maybe [Text]
forall a. a -> Maybe a
Just ([Text] -> Maybe [Text])
-> (String -> [Text]) -> String -> Maybe [Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (if Bool
mark_exception then String -> [Text]
exceptionLines else String -> [Text]
errorLines) (String -> Maybe [Text]) -> String -> Maybe [Text]
forall a b. (a -> b) -> a -> b
$ String
err
Right Maybe String
x -> String -> [Text]
singleLine (String -> [Text]) -> Maybe String -> Maybe [Text]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe String
x
String -> Maybe [Text] -> Ghc ()
forall (m :: * -> *) a1 a2.
(MonadIO m, Show a1, Show a2) =>
a1 -> a2 -> m ()
dbg String
"STMT} -> " Maybe [Text]
r
Maybe [Text] -> Ghc (Maybe [Text])
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe [Text]
r
|
DynFlags -> String -> Bool
isImport DynFlags
pf String
stmt =
do
String -> String -> Ghc ()
forall (m :: * -> *) a1 a2.
(MonadIO m, Show a1, Show a2) =>
a1 -> a2 -> m ()
dbg String
"{IMPORT " String
stmt
[InteractiveImport]
_ <- String -> Ghc [InteractiveImport]
forall (m :: * -> *). GhcMonad m => String -> m [InteractiveImport]
addImport String
stmt
Maybe [Text] -> Ghc (Maybe [Text])
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe [Text]
forall a. Maybe a
Nothing
|
Bool
otherwise =
do
String -> String -> Ghc ()
forall (m :: * -> *) a1 a2.
(MonadIO m, Show a1, Show a2) =>
a1 -> a2 -> m ()
dbg String
"{DECL " String
stmt
Ghc [Name] -> Ghc ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (Ghc [Name] -> Ghc ()) -> Ghc [Name] -> Ghc ()
forall a b. (a -> b) -> a -> b
$ String -> Ghc [Name]
forall (m :: * -> *). GhcMonad m => String -> m [Name]
runDecls String
stmt
Maybe [Text] -> Ghc (Maybe [Text])
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe [Text]
forall a. Maybe a
Nothing
pf :: DynFlags
pf = DynFlags -> DynFlags
initParserOpts DynFlags
df
#if !MIN_VERSION_ghc(9,0,0)
unhelpfulReason :: p
unhelpfulReason = p
"<interactive>"
#else
unhelpfulReason = UnhelpfulInteractive
#endif
exec :: String -> EvalId -> Ghc (Either String (Maybe String))
exec String
stmt EvalId
l =
let opts :: ExecOptions
opts = ExecOptions
execOptions{execSourceFile :: String
execSourceFile = String
fp, execLineNumber :: EvalId
execLineNumber = EvalId
l}
in String -> ExecOptions -> Ghc (Either String (Maybe String))
myExecStmt String
stmt ExecOptions
opts
prettyWarn :: Warn -> String
prettyWarn :: Warn -> String
prettyWarn Warn{WarnReason
Located String
warnReason :: Warn -> WarnReason
warnMsg :: Located String
warnReason :: WarnReason
warnMsg :: Warn -> Located String
..} =
Text -> String
T.unpack (SrcSpan -> Text
forall a. Outputable a => a -> Text
printOutputable (SrcSpan -> Text) -> SrcSpan -> Text
forall a b. (a -> b) -> a -> b
$ Located String -> SrcSpan
forall a. HasSrcSpan a => a -> SrcSpan
SrcLoc.getLoc Located String
warnMsg) String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
": warning:\n"
String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
" " String -> String -> String
forall a. Semigroup a => a -> a -> a
<> Located String -> SrcSpanLess (Located String)
forall a. HasSrcSpan a => a -> SrcSpanLess a
SrcLoc.unLoc Located String
warnMsg
runGetSession :: MonadIO m => IdeState -> NormalizedFilePath -> m HscEnv
runGetSession :: IdeState -> NormalizedFilePath -> m HscEnv
runGetSession IdeState
st NormalizedFilePath
nfp = 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
$ String -> IdeState -> Action HscEnv -> IO HscEnv
forall a. String -> IdeState -> Action a -> IO a
runAction String
"eval" IdeState
st (Action HscEnv -> IO HscEnv) -> Action HscEnv -> IO HscEnv
forall a b. (a -> b) -> a -> b
$ do
IdeGhcSession{String -> IO (IdeResult HscEnvEq, [String])
loadSessionFun :: IdeGhcSession -> String -> IO (IdeResult HscEnvEq, [String])
loadSessionFun :: String -> IO (IdeResult HscEnvEq, [String])
loadSessionFun} <- GhcSessionIO -> Action IdeGhcSession
forall k v. IdeRule k v => k -> Action v
useNoFile_ GhcSessionIO
GhcSessionIO
let fp :: String
fp = NormalizedFilePath -> String
fromNormalizedFilePath NormalizedFilePath
nfp
(([FileDiagnostic]
_, Maybe HscEnvEq
res),[String]
_) <- IO (IdeResult HscEnvEq, [String])
-> Action (IdeResult HscEnvEq, [String])
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (IdeResult HscEnvEq, [String])
-> Action (IdeResult HscEnvEq, [String]))
-> IO (IdeResult HscEnvEq, [String])
-> Action (IdeResult HscEnvEq, [String])
forall a b. (a -> b) -> a -> b
$ String -> IO (IdeResult HscEnvEq, [String])
loadSessionFun String
fp
let env :: HscEnvEq
env = HscEnvEq -> Maybe HscEnvEq -> HscEnvEq
forall a. a -> Maybe a -> a
fromMaybe (String -> HscEnvEq
forall a. HasCallStack => String -> a
error (String -> HscEnvEq) -> String -> HscEnvEq
forall a b. (a -> b) -> a -> b
$ String
"Unknown file: " String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
fp) Maybe HscEnvEq
res
ghcSessionDepsConfig :: GhcSessionDepsConfig
ghcSessionDepsConfig = GhcSessionDepsConfig
forall a. Default a => a
def
{ $sel:checkForImportCycles:GhcSessionDepsConfig :: Bool
checkForImportCycles = Bool
False
}
Maybe HscEnv
res <- (HscEnvEq -> HscEnv) -> Maybe HscEnvEq -> Maybe HscEnv
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap HscEnvEq -> HscEnv
hscEnvWithImportPaths (Maybe HscEnvEq -> Maybe HscEnv)
-> Action (Maybe HscEnvEq) -> Action (Maybe HscEnv)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Bool
-> GhcSessionDepsConfig
-> HscEnvEq
-> NormalizedFilePath
-> Action (Maybe HscEnvEq)
ghcSessionDepsDefinition Bool
True GhcSessionDepsConfig
ghcSessionDepsConfig HscEnvEq
env NormalizedFilePath
nfp
HscEnv -> Action HscEnv
forall (m :: * -> *) a. Monad m => a -> m a
return (HscEnv -> Action HscEnv) -> HscEnv -> Action HscEnv
forall a b. (a -> b) -> a -> b
$ HscEnv -> Maybe HscEnv -> HscEnv
forall a. a -> Maybe a -> a
fromMaybe (String -> HscEnv
forall a. HasCallStack => String -> a
error (String -> HscEnv) -> String -> HscEnv
forall a b. (a -> b) -> a -> b
$ String
"Unable to load file: " String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
fp) Maybe HscEnv
res
needsQuickCheck :: [(Section, Test)] -> Bool
needsQuickCheck :: [(Section, Test)] -> Bool
needsQuickCheck = ((Section, Test) -> Bool) -> [(Section, Test)] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (Test -> Bool
isProperty (Test -> Bool)
-> ((Section, Test) -> Test) -> (Section, Test) -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Section, Test) -> Test
forall a b. (a, b) -> b
snd)
hasQuickCheck :: DynFlags -> Bool
hasQuickCheck :: DynFlags -> Bool
hasQuickCheck DynFlags
df = DynFlags -> String -> Bool
hasPackage DynFlags
df String
"QuickCheck"
singleLine :: String -> [Text]
singleLine :: String -> [Text]
singleLine String
s = [String -> Text
T.pack String
s]
errorLines :: String -> [Text]
errorLines :: String -> [Text]
errorLines =
(Text -> Bool) -> [Text] -> [Text]
forall a. (a -> Bool) -> [a] -> [a]
dropWhileEnd Text -> Bool
T.null
([Text] -> [Text]) -> (String -> [Text]) -> String -> [Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text -> Bool) -> [Text] -> [Text]
forall a. (a -> Bool) -> [a] -> [a]
takeWhile (Bool -> Bool
not (Bool -> Bool) -> (Text -> Bool) -> Text -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text
"CallStack" Text -> Text -> Bool
`T.isPrefixOf`))
([Text] -> [Text]) -> (String -> [Text]) -> String -> [Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> [Text]
T.lines
(Text -> [Text]) -> (String -> Text) -> String -> [Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
T.pack
exceptionLines :: String -> [Text]
exceptionLines :: String -> [Text]
exceptionLines = (Index [Text] -> Traversal' [Text] (IxValue [Text])
forall m. Ixed m => Index m -> Traversal' m (IxValue m)
ix Index [Text]
0 ((Text -> Identity Text) -> [Text] -> Identity [Text])
-> (Text -> Text) -> [Text] -> [Text]
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
%~ (Text
"*** Exception: " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<>)) ([Text] -> [Text]) -> (String -> [Text]) -> String -> [Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> [Text]
errorLines
pad_ :: Text -> Text -> Text
pad_ :: Text -> Text -> Text
pad_ Text
prefix = (Text
prefix Text -> Text -> Text
`T.append`) (Text -> Text) -> (Text -> Text) -> Text -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
convertBlank
convertBlank :: Text -> Text
convertBlank :: Text -> Text
convertBlank Text
x
| Text -> Bool
T.null Text
x = Text
"<BLANKLINE>"
| Bool
otherwise = Text
x
padPrefix :: IsString p => Format -> p
padPrefix :: Format -> p
padPrefix Format
SingleLine = p
"-- "
padPrefix Format
_ = p
""
type GHCiLikeCmd = DynFlags -> Text -> Ghc (Maybe Text)
ghciLikeCommands :: [(Text, GHCiLikeCmd)]
ghciLikeCommands :: [(Text, GHCiLikeCmd)]
ghciLikeCommands =
[ (Text
"info", Bool -> GHCiLikeCmd
doInfoCmd Bool
False)
, (Text
"info!", Bool -> GHCiLikeCmd
doInfoCmd Bool
True)
, (Text
"kind", Bool -> GHCiLikeCmd
doKindCmd Bool
False)
, (Text
"kind!", Bool -> GHCiLikeCmd
doKindCmd Bool
True)
, (Text
"type", GHCiLikeCmd
doTypeCmd)
]
evalGhciLikeCmd :: Text -> Text -> Ghc (Maybe [Text])
evalGhciLikeCmd :: Text -> Text -> Ghc (Maybe [Text])
evalGhciLikeCmd Text
cmd Text
arg = do
DynFlags
df <- Ghc DynFlags
forall (m :: * -> *). GhcMonad m => m DynFlags
getSessionDynFlags
case Text -> [(Text, GHCiLikeCmd)] -> Maybe GHCiLikeCmd
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Text
cmd [(Text, GHCiLikeCmd)]
ghciLikeCommands
Maybe GHCiLikeCmd -> Maybe GHCiLikeCmd -> Maybe GHCiLikeCmd
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (Text, GHCiLikeCmd) -> GHCiLikeCmd
forall a b. (a, b) -> b
snd
((Text, GHCiLikeCmd) -> GHCiLikeCmd)
-> Maybe (Text, GHCiLikeCmd) -> Maybe GHCiLikeCmd
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ((Text, GHCiLikeCmd) -> Bool)
-> [(Text, GHCiLikeCmd)] -> Maybe (Text, GHCiLikeCmd)
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Maybe a
find (Text -> Text -> Bool
T.isPrefixOf Text
cmd (Text -> Bool)
-> ((Text, GHCiLikeCmd) -> Text) -> (Text, GHCiLikeCmd) -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text, GHCiLikeCmd) -> Text
forall a b. (a, b) -> a
fst) [(Text, GHCiLikeCmd)]
ghciLikeCommands of
Just GHCiLikeCmd
hndler ->
(Text -> [Text]) -> Maybe Text -> Maybe [Text]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap
Text -> [Text]
T.lines
(Maybe Text -> Maybe [Text])
-> Ghc (Maybe Text) -> Ghc (Maybe [Text])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GHCiLikeCmd
hndler DynFlags
df Text
arg
Maybe GHCiLikeCmd
_ -> GhciLikeCmdException -> Ghc (Maybe [Text])
forall a e. Exception e => e -> a
E.throw (GhciLikeCmdException -> Ghc (Maybe [Text]))
-> GhciLikeCmdException -> Ghc (Maybe [Text])
forall a b. (a -> b) -> a -> b
$ Text -> Text -> GhciLikeCmdException
GhciLikeCmdNotImplemented Text
cmd Text
arg
doInfoCmd :: Bool -> DynFlags -> Text -> Ghc (Maybe Text)
doInfoCmd :: Bool -> GHCiLikeCmd
doInfoCmd Bool
allInfo DynFlags
dflags Text
s = do
[SDoc]
sdocs <- (Text -> Ghc SDoc) -> [Text] -> Ghc [SDoc]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Text -> Ghc SDoc
forall (m :: * -> *). GhcMonad m => Text -> m SDoc
infoThing (Text -> [Text]
T.words Text
s)
Maybe Text -> Ghc (Maybe Text)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Maybe Text -> Ghc (Maybe Text)) -> Maybe Text -> Ghc (Maybe Text)
forall a b. (a -> b) -> a -> b
$ Text -> Maybe Text
forall a. a -> Maybe a
Just (Text -> Maybe Text) -> Text -> Maybe Text
forall a b. (a -> b) -> a -> b
$ String -> Text
T.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ DynFlags -> SDoc -> String
showSDoc DynFlags
dflags ([SDoc] -> SDoc
vcat [SDoc]
sdocs)
where
infoThing :: GHC.GhcMonad m => Text -> m SDoc
infoThing :: Text -> m SDoc
infoThing (Text -> String
T.unpack -> String
str) = do
[Name]
names <- String -> m [Name]
forall (m :: * -> *). GhcMonad m => String -> m [Name]
GHC.parseName String
str
[Maybe (TyThing, Fixity, [ClsInst], [FamInst], SDoc)]
mb_stuffs <- (Name -> m (Maybe (TyThing, Fixity, [ClsInst], [FamInst], SDoc)))
-> [Name]
-> m [Maybe (TyThing, Fixity, [ClsInst], [FamInst], SDoc)]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (Bool
-> Name -> m (Maybe (TyThing, Fixity, [ClsInst], [FamInst], SDoc))
forall (m :: * -> *).
GhcMonad m =>
Bool
-> Name -> m (Maybe (TyThing, Fixity, [ClsInst], [FamInst], SDoc))
GHC.getInfo Bool
allInfo) [Name]
names
let filtered :: [(TyThing, Fixity, [ClsInst], [FamInst], SDoc)]
filtered = ((TyThing, Fixity, [ClsInst], [FamInst], SDoc) -> TyThing)
-> [(TyThing, Fixity, [ClsInst], [FamInst], SDoc)]
-> [(TyThing, Fixity, [ClsInst], [FamInst], SDoc)]
forall a. (a -> TyThing) -> [a] -> [a]
filterOutChildren (\(TyThing
t,Fixity
_f,[ClsInst]
_ci,[FamInst]
_fi,SDoc
_sd) -> TyThing
t)
([Maybe (TyThing, Fixity, [ClsInst], [FamInst], SDoc)]
-> [(TyThing, Fixity, [ClsInst], [FamInst], SDoc)]
forall a. [Maybe a] -> [a]
catMaybes [Maybe (TyThing, Fixity, [ClsInst], [FamInst], SDoc)]
mb_stuffs)
SDoc -> m SDoc
forall (m :: * -> *) a. Monad m => a -> m a
return (SDoc -> m SDoc) -> SDoc -> m SDoc
forall a b. (a -> b) -> a -> b
$ [SDoc] -> SDoc
vcat (SDoc -> [SDoc] -> [SDoc]
forall a. a -> [a] -> [a]
intersperse (String -> SDoc
text String
"") ([SDoc] -> [SDoc]) -> [SDoc] -> [SDoc]
forall a b. (a -> b) -> a -> b
$ ((TyThing, Fixity, [ClsInst], [FamInst], SDoc) -> SDoc)
-> [(TyThing, Fixity, [ClsInst], [FamInst], SDoc)] -> [SDoc]
forall a b. (a -> b) -> [a] -> [b]
map (TyThing, Fixity, [ClsInst], [FamInst], SDoc) -> SDoc
pprInfo [(TyThing, Fixity, [ClsInst], [FamInst], SDoc)]
filtered)
filterOutChildren :: (a -> TyThing) -> [a] -> [a]
filterOutChildren :: (a -> TyThing) -> [a] -> [a]
filterOutChildren a -> TyThing
get_thing [a]
xs
= (a -> Bool) -> [a] -> [a]
forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not (Bool -> Bool) -> (a -> Bool) -> a -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Bool
has_parent) [a]
xs
where
all_names :: NameSet
all_names = [Name] -> NameSet
mkNameSet ((a -> Name) -> [a] -> [Name]
forall a b. (a -> b) -> [a] -> [b]
map (TyThing -> Name
forall a. NamedThing a => a -> Name
getName (TyThing -> Name) -> (a -> TyThing) -> a -> Name
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> TyThing
get_thing) [a]
xs)
has_parent :: a -> Bool
has_parent a
x = case TyThing -> Maybe TyThing
tyThingParent_maybe (a -> TyThing
get_thing a
x) of
Just TyThing
p -> TyThing -> Name
forall a. NamedThing a => a -> Name
getName TyThing
p Name -> NameSet -> Bool
`elemNameSet` NameSet
all_names
Maybe TyThing
Nothing -> Bool
False
pprInfo :: (TyThing, Fixity, [GHC.ClsInst], [GHC.FamInst], SDoc) -> SDoc
pprInfo :: (TyThing, Fixity, [ClsInst], [FamInst], SDoc) -> SDoc
pprInfo (TyThing
thing, Fixity
fixity, [ClsInst]
cls_insts, [FamInst]
fam_insts, SDoc
docs)
= SDoc
docs
SDoc -> SDoc -> SDoc
$$ TyThing -> SDoc
pprTyThingInContextLoc TyThing
thing
SDoc -> SDoc -> SDoc
$$ TyThing -> Fixity -> SDoc
showFixity TyThing
thing Fixity
fixity
SDoc -> SDoc -> SDoc
$$ [SDoc] -> SDoc
vcat ((ClsInst -> SDoc) -> [ClsInst] -> [SDoc]
forall a b. (a -> b) -> [a] -> [b]
map ClsInst -> SDoc
GHC.pprInstance [ClsInst]
cls_insts)
SDoc -> SDoc -> SDoc
$$ [SDoc] -> SDoc
vcat ((FamInst -> SDoc) -> [FamInst] -> [SDoc]
forall a b. (a -> b) -> [a] -> [b]
map FamInst -> SDoc
GHC.pprFamInst [FamInst]
fam_insts)
pprTyThingInContextLoc :: TyThing -> SDoc
pprTyThingInContextLoc :: TyThing -> SDoc
pprTyThingInContextLoc TyThing
tyThing
= SDoc -> SDoc -> SDoc
showWithLoc (Name -> SDoc
pprDefinedAt (TyThing -> Name
forall a. NamedThing a => a -> Name
getName TyThing
tyThing))
(ShowSub -> TyThing -> SDoc
pprTyThingInContext ShowSub
showToHeader TyThing
tyThing)
showWithLoc :: SDoc -> SDoc -> SDoc
showWithLoc :: SDoc -> SDoc -> SDoc
showWithLoc SDoc
loc SDoc
doc
= SDoc -> EvalId -> SDoc -> SDoc
hang SDoc
doc EvalId
2 (String -> SDoc
text String
"\t--" SDoc -> SDoc -> SDoc
<+> SDoc
loc)
showFixity :: TyThing -> Fixity -> SDoc
showFixity :: TyThing -> Fixity -> SDoc
showFixity TyThing
thing Fixity
fixity
| Fixity
fixity Fixity -> Fixity -> Bool
forall a. Eq a => a -> a -> Bool
/= Fixity
GHC.defaultFixity Bool -> Bool -> Bool
|| OccName -> Bool
isSymOcc (TyThing -> OccName
forall a. NamedThing a => a -> OccName
getOccName TyThing
thing)
= Fixity -> SDoc
forall a. Outputable a => a -> SDoc
ppr Fixity
fixity SDoc -> SDoc -> SDoc
<+> Name -> SDoc
forall a. (Outputable a, NamedThing a) => a -> SDoc
pprInfixName (TyThing -> Name
forall a. NamedThing a => a -> Name
GHC.getName TyThing
thing)
| Bool
otherwise = SDoc
empty
doKindCmd :: Bool -> DynFlags -> Text -> Ghc (Maybe Text)
doKindCmd :: Bool -> GHCiLikeCmd
doKindCmd Bool
False DynFlags
df Text
arg = do
let input :: Text
input = Text -> Text
T.strip Text
arg
(Type
_, Type
kind) <- Bool -> String -> Ghc (Type, Type)
forall (m :: * -> *).
GhcMonad m =>
Bool -> String -> m (Type, Type)
typeKind Bool
False (String -> Ghc (Type, Type)) -> String -> Ghc (Type, Type)
forall a b. (a -> b) -> a -> b
$ Text -> String
T.unpack Text
input
let kindText :: SDoc
kindText = String -> SDoc
text (Text -> String
T.unpack Text
input) SDoc -> SDoc -> SDoc
<+> SDoc
"::" SDoc -> SDoc -> SDoc
<+> Type -> SDoc
pprTypeForUser Type
kind
Maybe Text -> Ghc (Maybe Text)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Maybe Text -> Ghc (Maybe Text)) -> Maybe Text -> Ghc (Maybe Text)
forall a b. (a -> b) -> a -> b
$ Text -> Maybe Text
forall a. a -> Maybe a
Just (Text -> Maybe Text) -> Text -> Maybe Text
forall a b. (a -> b) -> a -> b
$ String -> Text
T.pack (DynFlags -> SDoc -> String
showSDoc DynFlags
df SDoc
kindText)
doKindCmd Bool
True DynFlags
df Text
arg = do
let input :: Text
input = Text -> Text
T.strip Text
arg
(Type
ty, Type
kind) <- Bool -> String -> Ghc (Type, Type)
forall (m :: * -> *).
GhcMonad m =>
Bool -> String -> m (Type, Type)
typeKind Bool
True (String -> Ghc (Type, Type)) -> String -> Ghc (Type, Type)
forall a b. (a -> b) -> a -> b
$ Text -> String
T.unpack Text
input
let kindDoc :: SDoc
kindDoc = String -> SDoc
text (Text -> String
T.unpack Text
input) SDoc -> SDoc -> SDoc
<+> SDoc
"::" SDoc -> SDoc -> SDoc
<+> Type -> SDoc
pprTypeForUser Type
kind
tyDoc :: SDoc
tyDoc = SDoc
"=" SDoc -> SDoc -> SDoc
<+> Type -> SDoc
pprTypeForUser Type
ty
Maybe Text -> Ghc (Maybe Text)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Maybe Text -> Ghc (Maybe Text)) -> Maybe Text -> Ghc (Maybe Text)
forall a b. (a -> b) -> a -> b
$ Text -> Maybe Text
forall a. a -> Maybe a
Just (Text -> Maybe Text) -> Text -> Maybe Text
forall a b. (a -> b) -> a -> b
$ String -> Text
T.pack (DynFlags -> SDoc -> String
showSDoc DynFlags
df (SDoc -> String) -> SDoc -> String
forall a b. (a -> b) -> a -> b
$ SDoc
kindDoc SDoc -> SDoc -> SDoc
$$ SDoc
tyDoc)
doTypeCmd :: DynFlags -> Text -> Ghc (Maybe Text)
doTypeCmd :: GHCiLikeCmd
doTypeCmd DynFlags
dflags Text
arg = do
let (TcRnExprMode
emod, Text
expr) = Text -> (TcRnExprMode, Text)
parseExprMode Text
arg
Type
ty <- TcRnExprMode -> String -> Ghc Type
forall (m :: * -> *).
GhcMonad m =>
TcRnExprMode -> String -> m Type
GHC.exprType TcRnExprMode
emod (String -> Ghc Type) -> String -> Ghc Type
forall a b. (a -> b) -> a -> b
$ Text -> String
T.unpack Text
expr
let rawType :: Text
rawType = Text -> Text
T.strip (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ String -> Text
T.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ DynFlags -> SDoc -> String
showSDoc DynFlags
dflags (SDoc -> String) -> SDoc -> String
forall a b. (a -> b) -> a -> b
$ Type -> SDoc
pprTypeForUser Type
ty
broken :: Bool
broken = (Char -> Bool) -> Text -> Bool
T.any (\Char
c -> Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'\r' Bool -> Bool -> Bool
|| Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'\n') Text
rawType
Maybe Text -> Ghc (Maybe Text)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Maybe Text -> Ghc (Maybe Text)) -> Maybe Text -> Ghc (Maybe Text)
forall a b. (a -> b) -> a -> b
$
Text -> Maybe Text
forall a. a -> Maybe a
Just (Text -> Maybe Text) -> Text -> Maybe Text
forall a b. (a -> b) -> a -> b
$
if Bool
broken
then
String -> Text
T.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$
DynFlags -> SDoc -> String
showSDoc DynFlags
dflags (SDoc -> String) -> SDoc -> String
forall a b. (a -> b) -> a -> b
$
String -> SDoc
text (Text -> String
T.unpack Text
expr)
SDoc -> SDoc -> SDoc
$$ EvalId -> SDoc -> SDoc
nest EvalId
2 (SDoc
"::" SDoc -> SDoc -> SDoc
<+> Type -> SDoc
pprTypeForUser Type
ty)
else Text
expr Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" :: " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
rawType Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"\n"
parseExprMode :: Text -> (TcRnExprMode, T.Text)
parseExprMode :: Text -> (TcRnExprMode, Text)
parseExprMode Text
rawArg = case (Char -> Bool) -> Text -> (Text, Text)
T.break Char -> Bool
isSpace Text
rawArg of
#if !MIN_VERSION_ghc(9,2,0)
(Text
"+v", Text
rest) -> (TcRnExprMode
TM_NoInst, Text -> Text
T.strip Text
rest)
#endif
(Text
"+d", Text
rest) -> (TcRnExprMode
TM_Default, Text -> Text
T.strip Text
rest)
(Text, Text)
_ -> (TcRnExprMode
TM_Inst, Text
rawArg)
data GhciLikeCmdException = GhciLikeCmdNotImplemented
{ GhciLikeCmdException -> Text
ghciCmdName :: Text
, GhciLikeCmdException -> Text
ghciCmdArg :: Text
}
deriving (Typeable)
instance Show GhciLikeCmdException where
showsPrec :: EvalId -> GhciLikeCmdException -> String -> String
showsPrec EvalId
_ GhciLikeCmdNotImplemented{Text
ghciCmdArg :: Text
ghciCmdName :: Text
$sel:ghciCmdArg:GhciLikeCmdNotImplemented :: GhciLikeCmdException -> Text
$sel:ghciCmdName:GhciLikeCmdNotImplemented :: GhciLikeCmdException -> Text
..} =
String -> String -> String
showString String
"unknown command '"
(String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> String -> String
showString (Text -> String
T.unpack Text
ghciCmdName)
(String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> String -> String
showChar Char
'\''
instance E.Exception GhciLikeCmdException
parseGhciLikeCmd :: Text -> Maybe (Text, Text)
parseGhciLikeCmd :: Text -> Maybe (Text, Text)
parseGhciLikeCmd Text
input = do
(Char
':', Text
rest) <- Text -> Maybe (Char, Text)
T.uncons (Text -> Maybe (Char, Text)) -> Text -> Maybe (Char, Text)
forall a b. (a -> b) -> a -> b
$ Text -> Text
T.stripStart Text
input
(Text, Text) -> Maybe (Text, Text)
forall (f :: * -> *) a. Applicative f => a -> f a
pure ((Text, Text) -> Maybe (Text, Text))
-> (Text, Text) -> Maybe (Text, Text)
forall a b. (a -> b) -> a -> b
$ (Text -> Text) -> (Text, Text) -> (Text, Text)
forall (a :: * -> * -> *) b c d.
Arrow a =>
a b c -> a (d, b) (d, c)
second Text -> Text
T.strip ((Text, Text) -> (Text, Text)) -> (Text, Text) -> (Text, Text)
forall a b. (a -> b) -> a -> b
$ (Char -> Bool) -> Text -> (Text, Text)
T.break Char -> Bool
isSpace Text
rest
setupDynFlagsForGHCiLike :: HscEnv -> DynFlags -> IO DynFlags
setupDynFlagsForGHCiLike :: HscEnv -> DynFlags -> IO DynFlags
setupDynFlagsForGHCiLike HscEnv
env DynFlags
dflags = do
let dflags3 :: DynFlags
dflags3 = DynFlags -> DynFlags
setInterpreterLinkerOptions DynFlags
dflags
platform :: Platform
platform = DynFlags -> Platform
targetPlatform DynFlags
dflags3
evalWays :: Ways
evalWays = Ways
Compat.hostFullWays
dflags3a :: DynFlags
dflags3a = Ways -> DynFlags -> DynFlags
setWays Ways
evalWays DynFlags
dflags3
dflags3b :: DynFlags
dflags3b =
(DynFlags -> GeneralFlag -> DynFlags)
-> DynFlags -> [GeneralFlag] -> DynFlags
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl DynFlags -> GeneralFlag -> DynFlags
gopt_set DynFlags
dflags3a ([GeneralFlag] -> DynFlags) -> [GeneralFlag] -> DynFlags
forall a b. (a -> b) -> a -> b
$
(Way -> [GeneralFlag]) -> Ways -> [GeneralFlag]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (Platform -> Way -> [GeneralFlag]
Compat.wayGeneralFlags Platform
platform) Ways
evalWays
dflags3c :: DynFlags
dflags3c =
(DynFlags -> GeneralFlag -> DynFlags)
-> DynFlags -> [GeneralFlag] -> DynFlags
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl DynFlags -> GeneralFlag -> DynFlags
gopt_unset DynFlags
dflags3b ([GeneralFlag] -> DynFlags) -> [GeneralFlag] -> DynFlags
forall a b. (a -> b) -> a -> b
$
(Way -> [GeneralFlag]) -> Ways -> [GeneralFlag]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (Platform -> Way -> [GeneralFlag]
Compat.wayUnsetGeneralFlags Platform
platform) Ways
evalWays
dflags4 :: DynFlags
dflags4 =
DynFlags
dflags3c
DynFlags -> GeneralFlag -> DynFlags
`gopt_set` GeneralFlag
Opt_ImplicitImportQualified
DynFlags -> GeneralFlag -> DynFlags
`gopt_set` GeneralFlag
Opt_IgnoreOptimChanges
DynFlags -> GeneralFlag -> DynFlags
`gopt_set` GeneralFlag
Opt_IgnoreHpcChanges
DynFlags -> GeneralFlag -> DynFlags
`gopt_unset` GeneralFlag
Opt_DiagnosticsShowCaret
HscEnv -> DynFlags
Compat.hsc_dflags (HscEnv -> DynFlags) -> IO HscEnv -> IO DynFlags
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> HscEnv -> IO HscEnv
Compat.initializePlugins (DynFlags -> HscEnv -> HscEnv
Compat.hscSetFlags DynFlags
dflags4 HscEnv
env)