1+ {-# LANGUAGE LambdaCase #-}
12{-# LANGUAGE OverloadedStrings #-}
23{-# OPTIONS_GHC -Wwarn -fno-warn-orphans #-}
34
45-- | 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
67
78import Control.Lens ((^.) )
89import Data.Algorithm.Diff (Diff , PolyDiff (.. ), getDiff )
910import qualified Data.List.NonEmpty as NE
1011import Data.String (IsString )
1112import qualified Data.Text as T
1213import Development.IDE.Types.Location (Position (.. ), Range (.. ))
13- import GHC (InteractiveImport (IIDecl ), compileExpr )
14+ import GHC (ExecOptions , ExecResult (.. ),
15+ execStmt )
1416import GHC.LanguageExtensions.Type (Extension (.. ))
15- import GhcMonad (Ghc , GhcMonad , liftIO )
17+ import GhcMonad (Ghc , liftIO , modifySession )
18+ import HscTypes
1619import Ide.Plugin.Eval.Types (Language (Plain ), Loc ,
1720 Located (.. ),
1821 Section (sectionLanguage ),
1922 Test (.. ), Txt , locate ,
2023 locate0 )
21- import InteractiveEval (getContext , parseImportDecl , runDecls , setContext )
24+ import InteractiveEval (getContext , parseImportDecl ,
25+ runDecls , setContext )
2226import Language.LSP.Types.Lens (line , start )
23- import Unsafe.Coerce ( unsafeCoerce )
27+ import System.IO.Extra ( newTempFile , readFile' )
2428
2529-- | Return the ranges of the expression and result parts of the given test
2630testRanges :: Test -> (Range , Range )
@@ -77,12 +81,6 @@ asStmts (Example e _ _) = NE.toList e
7781asStmts (Property t _ _) =
7882 [" prop11 = " ++ t, " (propEvaluation prop11 :: IO String)" ]
7983
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-
8684-- | GHC extensions required for expression evaluation
8785evalExtensions :: [Extension ]
8886evalExtensions =
@@ -99,12 +97,19 @@ evalSetup = do
9997 preludeAsP <- parseImportDecl " import qualified Prelude as P"
10098 context <- getContext
10199 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
108113
109114{- | GHC declarations required to execute test properties
110115
0 commit comments