Skip to content

Commit 5aca051

Browse files
committed
Add diff option for eval plugin
1 parent f0bbc39 commit 5aca051

File tree

5 files changed

+48
-16
lines changed

5 files changed

+48
-16
lines changed

plugins/hls-eval-plugin/hls-eval-plugin.cabal

+1
Original file line numberDiff line numberDiff line change
@@ -45,6 +45,7 @@ library
4545
other-modules:
4646
Ide.Plugin.Eval.Code
4747
Ide.Plugin.Eval.CodeLens
48+
Ide.Plugin.Eval.Config
4849
Ide.Plugin.Eval.GHC
4950
Ide.Plugin.Eval.Parse.Comments
5051
Ide.Plugin.Eval.Parse.Option

plugins/hls-eval-plugin/src/Ide/Plugin/Eval.hs

+9-3
Original file line numberDiff line numberDiff line change
@@ -11,17 +11,23 @@ module Ide.Plugin.Eval (
1111

1212
import Development.IDE (IdeState)
1313
import qualified Ide.Plugin.Eval.CodeLens as CL
14+
import Ide.Plugin.Eval.Config
1415
import Ide.Plugin.Eval.Rules (rules)
15-
import Ide.Types (PluginDescriptor (..), PluginId,
16+
import Ide.Types (ConfigDescriptor (..),
17+
PluginDescriptor (..), PluginId,
18+
defaultConfigDescriptor,
1619
defaultPluginDescriptor,
17-
mkPluginHandler)
20+
mkCustomConfig, mkPluginHandler)
1821
import Language.LSP.Types
1922

2023
-- |Plugin descriptor
2124
descriptor :: PluginId -> PluginDescriptor IdeState
2225
descriptor plId =
2326
(defaultPluginDescriptor plId)
2427
{ pluginHandlers = mkPluginHandler STextDocumentCodeLens CL.codeLens
25-
, pluginCommands = [CL.evalCommand]
28+
, pluginCommands = [CL.evalCommand plId]
2629
, pluginRules = rules
30+
, pluginConfigDescriptor = defaultConfigDescriptor
31+
{ configCustomConfig = mkCustomConfig properties
32+
}
2733
}

plugins/hls-eval-plugin/src/Ide/Plugin/Eval/Code.hs

+4-4
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,6 @@
11
{-# LANGUAGE LambdaCase #-}
2-
{-# LANGUAGE ViewPatterns #-}
32
{-# LANGUAGE OverloadedStrings #-}
3+
{-# LANGUAGE ViewPatterns #-}
44
{-# OPTIONS_GHC -Wwarn -fno-warn-orphans #-}
55

66
-- | Expression execution
@@ -59,9 +59,9 @@ showDiff (First w) = "WAS " <> w
5959
showDiff (Second w) = "NOW " <> w
6060
showDiff (Both w _) = w
6161

62-
testCheck :: (Section, Test) -> [T.Text] -> [T.Text]
63-
testCheck (section, test) out
64-
| null (testOutput test) || sectionLanguage section == Plain = out
62+
testCheck :: Bool -> (Section, Test) -> [T.Text] -> [T.Text]
63+
testCheck diff (section, test) out
64+
| not diff || null (testOutput test) || sectionLanguage section == Plain = out
6565
| otherwise = showDiffs $ getDiff (map T.pack $ testOutput test) out
6666

6767
testLengths :: Test -> (Int, Int)

plugins/hls-eval-plugin/src/Ide/Plugin/Eval/CodeLens.hs

+13-9
Original file line numberDiff line numberDiff line change
@@ -30,6 +30,7 @@ import qualified Control.Exception as E
3030
import Control.Lens (_1, _3, (%~), (<&>), (^.))
3131
import Control.Monad (guard, join, void, when)
3232
import Control.Monad.IO.Class (MonadIO (liftIO))
33+
import Control.Monad.Trans (lift)
3334
import Control.Monad.Trans.Except (ExceptT (..))
3435
import Data.Aeson (toJSON)
3536
import Data.Char (isSpace)
@@ -78,10 +79,12 @@ import qualified GHC.LanguageExtensions.Type as LangExt (Extension (..))
7879

7980
import Development.IDE.Core.FileStore (setSomethingModified)
8081
import Development.IDE.Types.Shake (toKey)
82+
import Ide.Plugin.Config (Config)
8183
import Ide.Plugin.Eval.Code (Statement, asStatements,
8284
evalSetup, myExecStmt,
8385
propSetup, resultRange,
8486
testCheck, testRanges)
87+
import Ide.Plugin.Eval.Config (getDiffProperty)
8588
import Ide.Plugin.Eval.GHC (addImport, addPackages,
8689
hasPackage, showDynFlags)
8790
import Ide.Plugin.Eval.Parse.Comments (commentsToSections)
@@ -176,16 +179,16 @@ codeLens st plId CodeLensParams{_textDocument} =
176179
evalCommandName :: CommandId
177180
evalCommandName = "evalCommand"
178181

179-
evalCommand :: PluginCommand IdeState
180-
evalCommand = PluginCommand evalCommandName "evaluate" runEvalCmd
182+
evalCommand :: PluginId -> PluginCommand IdeState
183+
evalCommand plId = PluginCommand evalCommandName "evaluate" (runEvalCmd plId)
181184

182185
type EvalId = Int
183186

184-
runEvalCmd :: CommandFunction IdeState EvalParams
185-
runEvalCmd st EvalParams{..} =
187+
runEvalCmd :: PluginId -> CommandFunction IdeState EvalParams
188+
runEvalCmd plId st EvalParams{..} =
186189
let dbg = logWith st
187190
perf = timed dbg
188-
cmd :: ExceptT String (LspM c) WorkspaceEdit
191+
cmd :: ExceptT String (LspM Config) WorkspaceEdit
189192
cmd = do
190193
let tests = map (\(a,_,b) -> (a,b)) $ testsBySection sections
191194

@@ -300,12 +303,13 @@ runEvalCmd st EvalParams{..} =
300303
-- Evaluation takes place 'inside' the module
301304
setContext [Compat.IIModule modName]
302305
Right <$> getSession
303-
306+
diff <- lift $ getDiffProperty plId
304307
edits <-
305308
perf "edits" $
306309
liftIO $
307310
evalGhcEnv hscEnv' $
308311
runTests
312+
diff
309313
(st, fp)
310314
tests
311315

@@ -347,8 +351,8 @@ testsBySection sections =
347351

348352
type TEnv = (IdeState, String)
349353

350-
runTests :: TEnv -> [(Section, Test)] -> Ghc [TextEdit]
351-
runTests e@(_st, _) tests = do
354+
runTests :: Bool -> TEnv -> [(Section, Test)] -> Ghc [TextEdit]
355+
runTests diff e@(_st, _) tests = do
352356
df <- getInteractiveDynFlags
353357
evalSetup
354358
when (hasQuickCheck df && needsQuickCheck tests) $ void $ evals e df propSetup
@@ -363,7 +367,7 @@ runTests e@(_st, _) tests = do
363367
rs <- runTest e df test
364368
dbg "TEST RESULTS" rs
365369

366-
let checkedResult = testCheck (section, test) rs
370+
let checkedResult = testCheck diff (section, test) rs
367371

368372
let edit = asEdit (sectionFormat section) test (map pad checkedResult)
369373
dbg "TEST EDIT" edit
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,21 @@
1+
{-# LANGUAGE FlexibleContexts #-}
2+
{-# LANGUAGE OverloadedLabels #-}
3+
{-# LANGUAGE OverloadedStrings #-}
4+
module Ide.Plugin.Eval.Config
5+
( properties
6+
, getDiffProperty
7+
) where
8+
9+
import Ide.Plugin.Config (Config)
10+
import Ide.Plugin.Properties
11+
import Ide.PluginUtils (usePropertyLsp)
12+
import Ide.Types (PluginId)
13+
import Language.LSP.Server (MonadLsp)
14+
15+
properties :: Properties '[ 'PropertyKey "diff" 'TBoolean]
16+
properties = emptyProperties
17+
& defineBooleanProperty #diff
18+
"Enable the diff output (WAS/NOW) of eval lenses" True
19+
20+
getDiffProperty :: (MonadLsp Config m) => PluginId -> m Bool
21+
getDiffProperty plId = usePropertyLsp #diff plId properties

0 commit comments

Comments
 (0)