Skip to content

Commit f86289e

Browse files
committed
Add tests for class plugin
1 parent fa3bc51 commit f86289e

11 files changed

+156
-1
lines changed

Diff for: haskell-language-server.cabal

+1
Original file line numberDiff line numberDiff line change
@@ -390,6 +390,7 @@ test-suite func-test
390390

391391
main-is: Main.hs
392392
other-modules:
393+
Class
393394
Command
394395
Completion
395396
Config

Diff for: test/functional/Class.hs

+73
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,73 @@
1+
{-# LANGUAGE LambdaCase #-}
2+
-- {-# LANGUAGE ViewPatterns #-}
3+
{-# LANGUAGE OverloadedStrings #-}
4+
{-# LANGUAGE ScopedTypeVariables #-}
5+
module Class
6+
( tests
7+
)
8+
where
9+
10+
import Control.Lens hiding ((<.>))
11+
import Control.Monad.IO.Class (MonadIO(liftIO))
12+
import qualified Data.ByteString.Lazy as BS
13+
import qualified Data.Text.Encoding as T
14+
import Language.Haskell.LSP.Test
15+
import Language.Haskell.LSP.Types hiding (_title, _command)
16+
import qualified Language.Haskell.LSP.Types.Lens as J
17+
import System.FilePath
18+
import Test.Hls.Util
19+
import Test.Tasty
20+
import Test.Tasty.Golden
21+
import Test.Tasty.HUnit
22+
23+
tests :: TestTree
24+
tests = testGroup
25+
"class"
26+
[ testCase "Produces addMinimalMethodPlaceholders code actions for one instance" $ do
27+
runSession hlsCommand fullCaps classPath $ do
28+
doc <- openDoc "T1.hs" "haskell"
29+
_ <- waitForDiagnosticsFromSource doc "typecheck"
30+
caResults <- getAllCodeActions doc
31+
liftIO $ map (^? _CACodeAction . J.title) caResults
32+
@?=
33+
[ Just "Add placeholders for '=='"
34+
, Just "Add placeholders for '/='"
35+
]
36+
, glodenTest "Creates a placeholder for '=='" "T1" "eq"
37+
$ \(eqAction:_) -> do
38+
executeCodeAction eqAction
39+
, glodenTest "Creates a placeholder for '/='" "T1" "ne"
40+
$ \(_:neAction:_) -> do
41+
executeCodeAction neAction
42+
, glodenTest "Creates a placeholder for 'fmap'" "T2" "fmap"
43+
$ \(_:_:fmapAction:_) -> do
44+
executeCodeAction fmapAction
45+
, glodenTest "Creates a placeholder for multiple methods 1" "T3" "1"
46+
$ \(mmAction:_) -> do
47+
executeCodeAction mmAction
48+
, glodenTest "Creates a placeholder for multiple methods 2" "T3" "2"
49+
$ \(_:mmAction:_) -> do
50+
executeCodeAction mmAction
51+
]
52+
53+
_CACodeAction :: Prism' CAResult CodeAction
54+
_CACodeAction = prism' CACodeAction $ \case
55+
CACodeAction action -> Just action
56+
_ -> Nothing
57+
58+
classPath :: FilePath
59+
classPath = "test" </> "testdata" </> "class"
60+
61+
glodenTest :: String -> FilePath -> FilePath -> ([CodeAction] -> Session ()) -> TestTree
62+
glodenTest name fp deco execute
63+
= goldenVsStringDiff name goldenGitDiff (classPath </> fp <.> deco <.> "expected" <.> "hs")
64+
$ runSession hlsCommand fullCaps classPath
65+
$ do
66+
doc <- openDoc (fp <.> "hs") "haskell"
67+
_ <- waitForDiagnosticsFromSource doc "typecheck"
68+
actions <- concatMap (^.. _CACodeAction) <$> getAllCodeActions doc
69+
execute actions
70+
BS.fromStrict . T.encodeUtf8 <$> getDocumentEdit doc
71+
72+
goldenGitDiff :: FilePath -> FilePath -> [String]
73+
goldenGitDiff fRef fNew = ["git", "diff", "--no-index", "--text", "--exit-code", fRef, fNew]

Diff for: test/functional/Main.hs

+3-1
Original file line numberDiff line numberDiff line change
@@ -7,6 +7,7 @@ import Test.Tasty.Runners ( listingTests
77
import Test.Tasty.Ingredients.Rerun
88
import Test.Tasty.Runners.AntXML
99

10+
import Class
1011
import Command
1112
import Config
1213
import Completion
@@ -36,7 +37,8 @@ main =
3637
[antXMLRunner, rerunningTests [listingTests, consoleTestReporter]]
3738
$ testGroup
3839
"haskell-language-server"
39-
[ Command.tests
40+
[ Class.tests
41+
, Command.tests
4042
, Completion.tests
4143
, Config.tests
4244
, Deferred.tests

Diff for: test/testdata/class/T1.eq.expected.hs

+6
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,6 @@
1+
module T1 where
2+
3+
data X = X
4+
5+
instance Eq X where
6+
(==) = _

Diff for: test/testdata/class/T1.hs

+5
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,5 @@
1+
module T1 where
2+
3+
data X = X
4+
5+
instance Eq X where

Diff for: test/testdata/class/T1.ne.expected.hs

+6
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,6 @@
1+
module T1 where
2+
3+
data X = X
4+
5+
instance Eq X where
6+
(/=) = _

Diff for: test/testdata/class/T2.fmap.expected.hs

+13
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,13 @@
1+
module T2 where
2+
3+
data X a
4+
= A a
5+
| B
6+
7+
instance
8+
(Eq a) => Eq (X a)
9+
where
10+
11+
instance
12+
Functor X where
13+
fmap = _

Diff for: test/testdata/class/T2.hs

+12
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,12 @@
1+
module T2 where
2+
3+
data X a
4+
= A a
5+
| B
6+
7+
instance
8+
(Eq a) => Eq (X a)
9+
where
10+
11+
instance
12+
Functor X

Diff for: test/testdata/class/T3.1.expected.hs

+13
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,13 @@
1+
module T3 where
2+
3+
class Test a where
4+
f :: a
5+
f = h
6+
g :: a
7+
h :: a
8+
h = f
9+
{-# MINIMAL f, g | g, h #-}
10+
11+
instance Test [a] where
12+
f = _
13+
g = _

Diff for: test/testdata/class/T3.2.expected.hs

+13
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,13 @@
1+
module T3 where
2+
3+
class Test a where
4+
f :: a
5+
f = h
6+
g :: a
7+
h :: a
8+
h = f
9+
{-# MINIMAL f, g | g, h #-}
10+
11+
instance Test [a] where
12+
g = _
13+
h = _

Diff for: test/testdata/class/T3.hs

+11
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,11 @@
1+
module T3 where
2+
3+
class Test a where
4+
f :: a
5+
f = h
6+
g :: a
7+
h :: a
8+
h = f
9+
{-# MINIMAL f, g | g, h #-}
10+
11+
instance Test [a] where

0 commit comments

Comments
 (0)