Skip to content

Commit 0701f3c

Browse files
committed
Tests
1 parent e881e50 commit 0701f3c

12 files changed

+150
-1
lines changed

haskell-language-server.cabal

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -275,6 +275,7 @@ test-suite func-test
275275
, Deferred
276276
, Definition
277277
, Diagnostic
278+
, Eval
278279
, Format
279280
, FunctionalBadProject
280281
, FunctionalCodeAction

test/functional/Eval.hs

Lines changed: 66 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,66 @@
1+
{-# LANGUAGE NamedFieldPuns #-}
2+
{-# LANGUAGE OverloadedStrings #-}
3+
{-# LANGUAGE ScopedTypeVariables #-}
4+
5+
module Eval (tests) where
6+
7+
import Control.Applicative.Combinators (skipManyTill)
8+
import Control.Monad.IO.Class (MonadIO (liftIO))
9+
import qualified Data.Text.IO as T
10+
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 System.FilePath
16+
import Test.Hls.Util
17+
import Test.Tasty
18+
import Test.Tasty.HUnit
19+
20+
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" ("T1.hs.expected"),
50+
testCase "Reevaluation of expressions" $ goldenTest "T2.hs" ("T2.hs.expected"),
51+
testCase "Evaluation of expressions w/ imports" $ goldenTest "T3.hs" ("T3.hs.expected"),
52+
testCase "Evaluation of expressions w/ lets" $ goldenTest "T4.hs" ("T4.hs.expected")
53+
]
54+
55+
goldenTest :: FilePath -> FilePath -> IO ()
56+
goldenTest input expected = runSession hieCommand fullCaps evalPath $ do
57+
doc <- openDoc input "haskell"
58+
[CodeLens {_command = Just c}] <- getCodeLenses doc
59+
executeCommand c
60+
_resp :: ApplyWorkspaceEditRequest <- skipManyTill anyMessage message
61+
edited <- documentContents doc
62+
expected <- liftIO $ T.readFile $ evalPath </> expected
63+
liftIO $ edited @?= expected
64+
65+
evalPath :: FilePath
66+
evalPath = "test/testdata/eval"

test/functional/Main.hs

Lines changed: 3 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -10,6 +10,7 @@ import Completion
1010
import Deferred
1111
import Definition
1212
import Diagnostic
13+
import Eval
1314
import Format
1415
import FunctionalBadProject
1516
import FunctionalCodeAction
@@ -36,6 +37,7 @@ main =
3637
, Deferred.tests
3738
, Definition.tests
3839
, Diagnostic.tests
40+
, Eval.tests
3941
, Format.tests
4042
, FunctionalBadProject.tests
4143
, FunctionalCodeAction.tests
@@ -47,4 +49,4 @@ main =
4749
, Rename.tests
4850
, Symbol.tests
4951
, TypeDefinition.tests
50-
]
52+
]

test/testdata/eval/T1.hs

Lines changed: 7 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,7 @@
1+
module T1 where
2+
3+
import Data.List (unwords)
4+
5+
-- >>> unwords example
6+
example :: [String]
7+
example = ["This","is","an","example","of","evaluation"]

test/testdata/eval/T1.hs.expected

Lines changed: 8 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,8 @@
1+
module T1 where
2+
3+
import Data.List (unwords)
4+
5+
-- >>> unwords example
6+
-- "This is an example of evaluation"
7+
example :: [String]
8+
example = ["This","is","an","example","of","evaluation"]

test/testdata/eval/T2.hs

Lines changed: 8 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,8 @@
1+
module T2 where
2+
3+
import Data.List (unwords)
4+
5+
-- >>> unwords example
6+
-- "Stale output"
7+
example :: [String]
8+
example = ["This","is","an","example","of","evaluation"]

test/testdata/eval/T2.hs.expected

Lines changed: 8 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,8 @@
1+
module T2 where
2+
3+
import Data.List (unwords)
4+
5+
-- >>> unwords example
6+
-- "This is an example of evaluation"
7+
example :: [String]
8+
example = ["This","is","an","example","of","evaluation"]

test/testdata/eval/T3.hs

Lines changed: 7 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,7 @@
1+
module T3 where
2+
3+
4+
-- >>> import Data.List (unwords)
5+
-- >>> unwords example
6+
example :: [String]
7+
example = ["This","is","an","example","of","evaluation"]

test/testdata/eval/T3.hs.expected

Lines changed: 8 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,8 @@
1+
module T3 where
2+
3+
4+
-- >>> import Data.List (unwords)
5+
-- >>> unwords example
6+
-- "This is an example of evaluation"
7+
example :: [String]
8+
example = ["This","is","an","example","of","evaluation"]

test/testdata/eval/T4.hs

Lines changed: 8 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,8 @@
1+
module T4 where
2+
3+
import Data.List (unwords)
4+
5+
-- >>> let evaluation = " evaluation"
6+
-- >>> unwords example ++ evaluation
7+
example :: [String]
8+
example = ["This","is","an","example","of"]

test/testdata/eval/T4.hs.expected

Lines changed: 9 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,9 @@
1+
module T4 where
2+
3+
import Data.List (unwords)
4+
5+
-- >>> let evaluation = " evaluation"
6+
-- >>> unwords example ++ evaluation
7+
-- "This is an example of evaluation"
8+
example :: [String]
9+
example = ["This","is","an","example","of"]

test/testdata/eval/test.cabal

Lines changed: 17 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,17 @@
1+
name: test
2+
version: 0.1.0.0
3+
-- synopsis:
4+
-- description:
5+
license: BSD3
6+
author: Author name here
7+
maintainer: [email protected]
8+
copyright: 2017 Author name here
9+
category: Web
10+
build-type: Simple
11+
cabal-version: >=1.10
12+
13+
library
14+
exposed-modules: T1, T2, T3, T4
15+
build-depends: base >= 4.7 && < 5
16+
default-language: Haskell2010
17+
ghc-options: -Wall -fwarn-unused-imports

0 commit comments

Comments
 (0)