1
+ {-# LANGUAGE LambdaCase #-}
1
2
{-# LANGUAGE OverloadedStrings #-}
2
3
{-# OPTIONS_GHC -Wwarn -fno-warn-orphans #-}
3
4
4
5
-- | Expression execution
5
- module Ide.Plugin.Eval.Code (Statement , testRanges , resultRange , evalExtensions , evalSetup , evalExpr , propSetup , testCheck , asStatements ) where
6
+ module Ide.Plugin.Eval.Code (Statement , testRanges , resultRange , evalExtensions , evalSetup , propSetup , testCheck , asStatements , myExecStmt ) where
6
7
7
8
import Control.Lens ((^.) )
8
9
import Data.Algorithm.Diff (Diff , PolyDiff (.. ), getDiff )
9
10
import qualified Data.List.NonEmpty as NE
10
11
import Data.String (IsString )
11
12
import qualified Data.Text as T
12
13
import Development.IDE.Types.Location (Position (.. ), Range (.. ))
13
- import GHC (InteractiveImport (IIDecl ), compileExpr )
14
+ import GHC (ExecOptions , ExecResult (.. ),
15
+ execStmt )
14
16
import GHC.LanguageExtensions.Type (Extension (.. ))
15
- import GhcMonad (Ghc , GhcMonad , liftIO )
17
+ import GhcMonad (Ghc , liftIO , modifySession )
18
+ import HscTypes
16
19
import Ide.Plugin.Eval.Types (Language (Plain ), Loc ,
17
20
Located (.. ),
18
21
Section (sectionLanguage ),
19
22
Test (.. ), Txt , locate ,
20
23
locate0 )
21
- import InteractiveEval (getContext , parseImportDecl , runDecls , setContext )
24
+ import InteractiveEval (getContext , parseImportDecl ,
25
+ runDecls , setContext )
22
26
import Language.LSP.Types.Lens (line , start )
23
- import Unsafe.Coerce ( unsafeCoerce )
27
+ import System.IO.Extra ( newTempFile , readFile' )
24
28
25
29
-- | Return the ranges of the expression and result parts of the given test
26
30
testRanges :: Test -> (Range , Range )
@@ -77,12 +81,6 @@ asStmts (Example e _ _) = NE.toList e
77
81
asStmts (Property t _ _) =
78
82
[" prop11 = " ++ t, " (propEvaluation prop11 :: IO String)" ]
79
83
80
- -- | Evaluate an expression (either a pure expression or an IO a)
81
- evalExpr :: GhcMonad m => [Char ] -> m String
82
- evalExpr e = do
83
- res <- compileExpr $ " asPrint (" ++ e ++ " )"
84
- liftIO (unsafeCoerce res :: IO String )
85
-
86
84
-- | GHC extensions required for expression evaluation
87
85
evalExtensions :: [Extension ]
88
86
evalExtensions =
@@ -99,12 +97,19 @@ evalSetup = do
99
97
preludeAsP <- parseImportDecl " import qualified Prelude as P"
100
98
context <- getContext
101
99
setContext (IIDecl preludeAsP : context)
102
- mapM_
103
- runDecls
104
- [ " class Print f where asPrint :: f -> P.IO P.String"
105
- , " instance P.Show a => Print (P.IO a) where asPrint io = io P.>>= P.return P.. P.show"
106
- , " instance P.Show a => Print a where asPrint a = P.return (P.show a)"
107
- ]
100
+
101
+ -- | A wrapper of 'InteractiveEval.execStmt', capturing the execution result
102
+ myExecStmt :: String -> ExecOptions -> Ghc (Either String (Maybe String ))
103
+ myExecStmt stmt opts = do
104
+ (temp, purge) <- liftIO newTempFile
105
+ evalPrint <- head <$> runDecls (" evalPrint x = P.writeFile " <> show temp <> " (P.show x)" )
106
+ modifySession $ \ hsc -> hsc {hsc_IC = setInteractivePrintName (hsc_IC hsc) evalPrint}
107
+ result <- execStmt stmt opts >>= \ case
108
+ ExecComplete (Left err) _ -> pure $ Left $ show err
109
+ ExecComplete (Right _) _ -> liftIO $ Right . (\ x -> if null x then Nothing else Just x) <$> readFile' temp
110
+ ExecBreak {} -> pure $ Right $ Just " breakpoints are not supported"
111
+ liftIO purge
112
+ pure result
108
113
109
114
{- | GHC declarations required to execute test properties
110
115
0 commit comments