21
21
-- [1] - https://github.com/jyp/dante
22
22
module Ide.Plugin.Eval where
23
23
24
+ import Control.Arrow (second )
25
+ import qualified Control.Exception as E
26
+ import Control.DeepSeq ( NFData
27
+ , deepseq
28
+ )
24
29
import Control.Monad (void )
25
30
import Control.Monad.IO.Class (MonadIO (liftIO ))
26
31
import Control.Monad.Trans.Class (MonadTrans (lift ))
@@ -29,7 +34,9 @@ import Control.Monad.Trans.Except (ExceptT (..), runExceptT,
29
34
import Data.Aeson (FromJSON , ToJSON , Value (Null ),
30
35
toJSON )
31
36
import Data.Bifunctor (Bifunctor (first ))
37
+ import Data.Char (isSpace )
32
38
import qualified Data.HashMap.Strict as Map
39
+ import Data.Maybe (catMaybes )
33
40
import Data.String (IsString (fromString ))
34
41
import Data.Text (Text )
35
42
import qualified Data.Text as T
@@ -44,14 +51,15 @@ import Development.IDE.Types.Location (toNormalizedFilePath',
44
51
uriToFilePath' )
45
52
import DynamicLoading (initializePlugins )
46
53
import DynFlags (targetPlatform )
47
- import GHC (DynFlags , ExecResult (.. ), GeneralFlag (Opt_IgnoreHpcChanges , Opt_IgnoreOptimChanges , Opt_ImplicitImportQualified ),
54
+ import GHC (Ghc , TcRnExprMode ( .. ), DynFlags , ExecResult (.. ), GeneralFlag (Opt_IgnoreHpcChanges , Opt_IgnoreOptimChanges , Opt_ImplicitImportQualified ),
48
55
GhcLink (LinkInMemory ),
49
56
GhcMode (CompManager ),
50
57
HscTarget (HscInterpreted ),
51
58
LoadHowMuch (LoadAllTargets ),
52
59
SuccessFlag (.. ),
53
60
execLineNumber , execOptions ,
54
61
execSourceFile , execStmt ,
62
+ exprType ,
55
63
getContext ,
56
64
getInteractiveDynFlags ,
57
65
getSession , getSessionDynFlags ,
@@ -77,17 +85,12 @@ import Ide.Types
77
85
import Language.Haskell.LSP.Core (LspFuncs (getVirtualFileFunc ))
78
86
import Language.Haskell.LSP.Types
79
87
import Language.Haskell.LSP.VFS (virtualFileText )
88
+ import Outputable (ppr , showSDoc )
80
89
import PrelNames (pRELUDE )
81
90
import System.FilePath
82
91
import System.IO (hClose )
83
92
import System.IO.Temp
84
- import Data.Maybe (catMaybes )
85
- import qualified Control.Exception as E
86
- import Control.DeepSeq ( NFData
87
- , deepseq
88
- )
89
- import Outputable (Outputable (ppr ), showSDoc )
90
- import Control.Applicative ((<|>) )
93
+ import Type.Reflection (Typeable )
91
94
92
95
descriptor :: PluginId -> PluginDescriptor
93
96
descriptor plId =
@@ -247,18 +250,8 @@ done, we want to switch back to GhcSessionDeps:
247
250
248
251
df <- liftIO $ evalGhcEnv hscEnv' getSessionDynFlags
249
252
let eval (stmt, l)
250
- | let stmt0 = T. strip $ T. pack stmt -- For stripping and de-prefixing
251
- , Just (reduce, type_) <-
252
- (True ,) <$> T. stripPrefix " :kind! " stmt0
253
- <|> (False ,) <$> T. stripPrefix " :kind " stmt0
254
- = do
255
- let input = T. strip type_
256
- (ty, kind) <- typeKind reduce $ T. unpack input
257
- pure $ Just
258
- $ T. unlines
259
- $ map (" -- " <> )
260
- $ (input <> " :: " <> T. pack (showSDoc df $ ppr kind))
261
- : [ " = " <> T. pack (showSDoc df $ ppr ty) | reduce]
253
+ | Just (cmd, arg) <- parseGhciLikeCmd $ T. pack stmt
254
+ = evalGhciLikeCmd cmd arg
262
255
| isStmt df stmt = do
263
256
-- set up a custom interactive print function
264
257
liftIO $ writeFile temp " "
@@ -309,6 +302,58 @@ done, we want to switch back to GhcSessionDeps:
309
302
310
303
return (WorkspaceApplyEdit , ApplyWorkspaceEditParams workspaceEdits)
311
304
305
+ evalGhciLikeCmd :: Text -> Text -> Ghc (Maybe Text )
306
+ evalGhciLikeCmd cmd arg = do
307
+ df <- getSessionDynFlags
308
+ let tppr = T. pack . showSDoc df . ppr
309
+ case cmd of
310
+ " kind" -> do
311
+ let input = T. strip arg
312
+ (_, kind) <- typeKind False $ T. unpack input
313
+ pure $ Just $ " -- " <> input <> " :: " <> tppr kind <> " \n "
314
+ " kind!" -> do
315
+ let input = T. strip arg
316
+ (ty, kind) <- typeKind True $ T. unpack input
317
+ pure
318
+ $ Just
319
+ $ T. unlines
320
+ $ map (" -- " <> )
321
+ [ input <> " :: " <> tppr kind
322
+ , " = " <> tppr ty
323
+ ]
324
+ " type" -> do
325
+ let (emod, expr) = parseExprMode arg
326
+ ty <- exprType emod $ T. unpack expr
327
+ pure $ Just $
328
+ " -- " <> expr <> " :: " <> tppr ty <> " \n "
329
+ _ -> E. throw $ GhciLikeCmdNotImplemented cmd arg
330
+
331
+ parseExprMode :: Text -> (TcRnExprMode , T. Text )
332
+ parseExprMode rawArg =
333
+ case T. break isSpace rawArg of
334
+ (" +v" , rest) -> (TM_NoInst , T. strip rest)
335
+ (" +d" , rest) -> (TM_Default , T. strip rest)
336
+ _ -> (TM_Inst , rawArg)
337
+
338
+ data GhciLikeCmdException =
339
+ GhciLikeCmdNotImplemented
340
+ { ghciCmdName :: Text
341
+ , ghciCmdArg :: Text
342
+ }
343
+ deriving (Typeable )
344
+
345
+ instance Show GhciLikeCmdException where
346
+ showsPrec _ GhciLikeCmdNotImplemented {.. } =
347
+ showString " unknown command '" .
348
+ showString (T. unpack ghciCmdName) . showChar ' \' '
349
+
350
+ instance E. Exception GhciLikeCmdException
351
+
352
+ parseGhciLikeCmd :: Text -> Maybe (Text , Text )
353
+ parseGhciLikeCmd input = do
354
+ (' :' , rest) <- T. uncons $ T. stripStart input
355
+ pure $ second T. strip $ T. break isSpace rest
356
+
312
357
strictTry :: NFData b => IO b -> IO (Either String b )
313
358
strictTry op = E. catch
314
359
(op >>= \ v -> return $! Right $! deepseq v v)
0 commit comments