Skip to content

Commit 04c2dfd

Browse files
committed
Test for fix of "Error from tests not reported"
1 parent 157cd40 commit 04c2dfd

File tree

3 files changed

+63
-46
lines changed

3 files changed

+63
-46
lines changed

Diff for: test/functional/Eval.hs

+56-46
Original file line numberDiff line numberDiff line change
@@ -2,63 +2,73 @@
22
{-# LANGUAGE OverloadedStrings #-}
33
{-# LANGUAGE ScopedTypeVariables #-}
44

5-
module Eval (tests) where
5+
module Eval
6+
( tests
7+
)
8+
where
69

7-
import Control.Applicative.Combinators (skipManyTill)
8-
import Control.Monad.IO.Class (MonadIO (liftIO))
9-
import qualified Data.Text.IO as T
10+
import Control.Applicative.Combinators
11+
( skipManyTill )
12+
import Control.Monad.IO.Class ( MonadIO(liftIO) )
13+
import qualified Data.Text.IO as T
1014
import Language.Haskell.LSP.Test
11-
import Language.Haskell.LSP.Types (ApplyWorkspaceEditRequest,
12-
CodeLens (CodeLens, _command, _range),
13-
Command (_title),
14-
Position (..), Range (..))
15+
import Language.Haskell.LSP.Types ( ApplyWorkspaceEditRequest
16+
, CodeLens
17+
( CodeLens
18+
, _command
19+
, _range
20+
)
21+
, Command(_title)
22+
, Position(..)
23+
, Range(..)
24+
)
1525
import System.FilePath
1626
import Test.Hls.Util
1727
import Test.Tasty
1828
import Test.Tasty.HUnit
1929

2030
tests :: TestTree
21-
tests =
22-
testGroup
23-
"eval"
24-
[ testCase "Produces Evaluate code lenses" $ do
25-
runSession hieCommand fullCaps evalPath $ do
26-
doc <- openDoc "T1.hs" "haskell"
27-
lenses <- getCodeLenses doc
28-
liftIO $ map (fmap _title . _command) lenses @?= [Just "Evaluate..."],
29-
testCase "Produces Refresh code lenses" $ do
30-
runSession hieCommand fullCaps evalPath $ do
31-
doc <- openDoc "T2.hs" "haskell"
32-
lenses <- getCodeLenses doc
33-
liftIO $ map (fmap _title . _command) lenses @?= [Just "Refresh..."],
34-
testCase "Code lenses have ranges" $ do
35-
runSession hieCommand fullCaps evalPath $ do
36-
doc <- openDoc "T1.hs" "haskell"
37-
lenses <- getCodeLenses doc
38-
liftIO $ map _range lenses @?= [Range (Position 4 0) (Position 4 15)],
39-
testCase "Multi-line expressions have a multi-line range" $ do
40-
runSession hieCommand fullCaps evalPath $ do
41-
doc <- openDoc "T3.hs" "haskell"
42-
lenses <- getCodeLenses doc
43-
liftIO $ map _range lenses @?= [Range (Position 3 0) (Position 4 15)],
44-
testCase "Executed expressions range covers only the expression" $ do
45-
runSession hieCommand fullCaps evalPath $ do
46-
doc <- openDoc "T2.hs" "haskell"
47-
lenses <- getCodeLenses doc
48-
liftIO $ map _range lenses @?= [Range (Position 4 0) (Position 4 15)],
49-
testCase "Evaluation of expressions" $ goldenTest "T1.hs",
50-
testCase "Reevaluation of expressions" $ goldenTest "T2.hs",
51-
testCase "Evaluation of expressions w/ imports" $ goldenTest "T3.hs",
52-
testCase "Evaluation of expressions w/ lets" $ goldenTest "T4.hs",
53-
testCase "Refresh an evaluation" $ goldenTest "T5.hs",
54-
testCase "Refresh an evaluation w/ lets" $ goldenTest "T6.hs",
55-
testCase "Refresh a multiline evaluation" $ goldenTest "T7.hs"
56-
]
31+
tests = testGroup
32+
"eval"
33+
[ testCase "Produces Evaluate code lenses" $ do
34+
runSession hieCommand fullCaps evalPath $ do
35+
doc <- openDoc "T1.hs" "haskell"
36+
lenses <- getCodeLenses doc
37+
liftIO $ map (fmap _title . _command) lenses @?= [Just "Evaluate..."]
38+
, testCase "Produces Refresh code lenses" $ do
39+
runSession hieCommand fullCaps evalPath $ do
40+
doc <- openDoc "T2.hs" "haskell"
41+
lenses <- getCodeLenses doc
42+
liftIO $ map (fmap _title . _command) lenses @?= [Just "Refresh..."]
43+
, testCase "Code lenses have ranges" $ do
44+
runSession hieCommand fullCaps evalPath $ do
45+
doc <- openDoc "T1.hs" "haskell"
46+
lenses <- getCodeLenses doc
47+
liftIO $ map _range lenses @?= [Range (Position 4 0) (Position 4 15)]
48+
, testCase "Multi-line expressions have a multi-line range" $ do
49+
runSession hieCommand fullCaps evalPath $ do
50+
doc <- openDoc "T3.hs" "haskell"
51+
lenses <- getCodeLenses doc
52+
liftIO $ map _range lenses @?= [Range (Position 3 0) (Position 4 15)]
53+
, testCase "Executed expressions range covers only the expression" $ do
54+
runSession hieCommand fullCaps evalPath $ do
55+
doc <- openDoc "T2.hs" "haskell"
56+
lenses <- getCodeLenses doc
57+
liftIO $ map _range lenses @?= [Range (Position 4 0) (Position 4 15)]
58+
, testCase "Evaluation of expressions" $ goldenTest "T1.hs"
59+
, testCase "Reevaluation of expressions" $ goldenTest "T2.hs"
60+
, testCase "Evaluation of expressions w/ imports" $ goldenTest "T3.hs"
61+
, testCase "Evaluation of expressions w/ lets" $ goldenTest "T4.hs"
62+
, testCase "Refresh an evaluation" $ goldenTest "T5.hs"
63+
, testCase "Refresh an evaluation w/ lets" $ goldenTest "T6.hs"
64+
, testCase "Refresh a multiline evaluation" $ goldenTest "T7.hs"
65+
, testCase "Evaluate incorrect expressions" $ goldenTest "T8.hs"
66+
]
5767

5868
goldenTest :: FilePath -> IO ()
5969
goldenTest input = runSession hieCommand fullCaps evalPath $ do
60-
doc <- openDoc input "haskell"
61-
[CodeLens {_command = Just c}] <- getCodeLenses doc
70+
doc <- openDoc input "haskell"
71+
[CodeLens { _command = Just c }] <- getCodeLenses doc
6272
executeCommand c
6373
_resp :: ApplyWorkspaceEditRequest <- skipManyTill anyMessage message
6474
edited <- documentContents doc

Diff for: test/testdata/eval/T8.hs

+3
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,3 @@
1+
module T8 where
2+
3+
-- >>> noFunctionWithThisName

Diff for: test/testdata/eval/T8.hs.expected

+4
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,4 @@
1+
module T8 where
2+
3+
-- >>> noFunctionWithThisName
4+
-- Variable not in scope: noFunctionWithThisName

0 commit comments

Comments
 (0)