1
- {-# LANGUAGE OverloadedStrings #-}
2
- {-# LANGUAGE ScopedTypeVariables #-}
3
- {-# LANGUAGE ViewPatterns #-}
4
- {-# LANGUAGE TypeOperators #-}
1
+ {-# LANGUAGE DataKinds #-}
5
2
{-# LANGUAGE DuplicateRecordFields #-}
6
- {-# LANGUAGE DataKinds #-}
3
+ {-# LANGUAGE OverloadedStrings #-}
4
+ {-# LANGUAGE ScopedTypeVariables #-}
5
+ {-# LANGUAGE TypeOperators #-}
6
+ {-# LANGUAGE ViewPatterns #-}
7
7
8
- module Tactic
9
- ( tests
10
- )
11
- where
8
+ module GoldenSpec where
12
9
13
10
import Control.Applicative.Combinators ( skipManyTill )
14
11
import Control.Lens hiding ((<.>) )
@@ -28,33 +25,18 @@ import Ide.Plugin.Tactic.FeatureSet (FeatureSet, allFeatures)
28
25
import Ide.Plugin.Tactic.TestTypes
29
26
import Language.LSP.Test
30
27
import Language.LSP.Types
31
- import Language.LSP.Types.Lens hiding (id , capabilities , message , executeCommand , applyEdit , rename )
28
+ import Language.LSP.Types.Lens hiding (id , capabilities , message , executeCommand , applyEdit , rename , line , title , name , actions )
32
29
import System.Directory (doesFileExist )
33
30
import System.FilePath
34
- import Test.Hls.Util
31
+ import Test.Hspec
35
32
import Test.Tasty
36
33
import Test.Tasty.ExpectedFailure (ignoreTestBecause )
37
34
import Test.Tasty.HUnit
35
+ import Test.Tasty.Ingredients.Rerun
36
+ import Test.Tasty.Runners (consoleTestReporter , listingTests )
37
+ import Test.Tasty.Runners.AntXML
38
38
39
39
40
- ------------------------------------------------------------------------------
41
- -- | Get a range at the given line and column corresponding to having nothing
42
- -- selected.
43
- --
44
- -- NB: These coordinates are in "file space", ie, 1-indexed.
45
- pointRange :: Int -> Int -> Range
46
- pointRange
47
- (subtract 1 -> line)
48
- (subtract 1 -> col) =
49
- Range (Position line col) (Position line $ col + 1 )
50
-
51
-
52
- ------------------------------------------------------------------------------
53
- -- | Get the title of a code action.
54
- codeActionTitle :: (Command |? CodeAction ) -> Maybe Text
55
- codeActionTitle InL {} = Nothing
56
- codeActionTitle (InR (CodeAction title _ _ _ _ _ _)) = Just title
57
-
58
40
59
41
tests :: TestTree
60
42
tests = testGroup
@@ -96,41 +78,72 @@ tests = testGroup
96
78
" T2.hs" 11 25
97
79
[ (not , DestructLambdaCase , " " )
98
80
]
99
- , goldenTest " GoldenIntros.hs" 2 8 Intros " "
100
- , goldenTest " GoldenEitherAuto.hs" 2 11 Auto " "
101
- , goldenTest " GoldenJoinCont.hs" 4 12 Auto " "
102
- , goldenTest " GoldenIdentityFunctor.hs" 3 11 Auto " "
103
- , goldenTest " GoldenIdTypeFam.hs" 7 11 Auto " "
104
- , goldenTest " GoldenEitherHomomorphic.hs" 2 15 Auto " "
105
- , goldenTest " GoldenNote.hs" 2 8 Auto " "
106
- , goldenTest " GoldenPureList.hs" 2 12 Auto " "
107
- , goldenTest " GoldenListFmap.hs" 2 12 Auto " "
108
- , goldenTest " GoldenFromMaybe.hs" 2 13 Auto " "
109
- , goldenTest " GoldenFoldr.hs" 2 10 Auto " "
110
- , goldenTest " GoldenSwap.hs" 2 8 Auto " "
111
- , goldenTest " GoldenFmapTree.hs" 4 11 Auto " "
112
- , goldenTest " GoldenGADTDestruct.hs" 7 17 Destruct " gadt"
113
- , goldenTest " GoldenGADTDestructCoercion.hs" 8 17 Destruct " gadt"
114
- , goldenTest " GoldenGADTAuto.hs" 7 13 Auto " "
115
- , goldenTest " GoldenSwapMany.hs" 2 12 Auto " "
116
- , goldenTest " GoldenBigTuple.hs" 4 12 Auto " "
117
- , goldenTest " GoldenShow.hs" 2 10 Auto " "
118
- , goldenTest " GoldenShowCompose.hs" 2 15 Auto " "
119
- , goldenTest " GoldenShowMapChar.hs" 2 8 Auto " "
120
- , goldenTest " GoldenSuperclass.hs" 7 8 Auto " "
81
+ , goldenTest " GoldenIntros.hs"
82
+ 2 8 Intros " "
83
+ , autoTest " GoldenEitherAuto.hs" 2 11
84
+ , autoTest " GoldenJoinCont.hs" 4 12
85
+ , autoTest " GoldenIdentityFunctor.hs" 3 11
86
+ , autoTest " GoldenIdTypeFam.hs" 7 11
87
+ , autoTest " GoldenEitherHomomorphic.hs" 2 15
88
+ , autoTest " GoldenNote.hs" 2 8
89
+ , autoTest " GoldenPureList.hs" 2 12
90
+ , autoTest " GoldenListFmap.hs" 2 12
91
+ , autoTest " GoldenFromMaybe.hs" 2 13
92
+ , autoTest " GoldenFoldr.hs" 2 10
93
+ , autoTest " GoldenSwap.hs" 2 8
94
+ , autoTest " GoldenFmapTree.hs" 4 11
95
+ , goldenTest " GoldenGADTDestruct.hs"
96
+ 7 17 Destruct " gadt"
97
+ , goldenTest " GoldenGADTDestructCoercion.hs"
98
+ 8 17 Destruct " gadt"
99
+ , autoTest " GoldenGADTAuto.hs" 7 13
100
+ , autoTest " GoldenSwapMany.hs" 2 12
101
+ , autoTest " GoldenBigTuple.hs" 4 12
102
+ , autoTest " GoldenShow.hs" 2 10
103
+ , autoTest " GoldenShowCompose.hs" 2 15
104
+ , autoTest " GoldenShowMapChar.hs" 2 8
105
+ , autoTest " GoldenSuperclass.hs" 7 8
121
106
, ignoreTestBecause " It is unreliable in circleci builds"
122
- $ goldenTest " GoldenApplicativeThen.hs" 2 11 Auto " "
123
- , goldenTest " GoldenSafeHead.hs" 2 12 Auto " "
124
- , expectFail " GoldenFish.hs" 5 18 Auto " "
125
- , goldenTest " GoldenArbitrary.hs" 25 13 Auto " "
126
- , goldenTest " FmapBoth.hs" 2 12 Auto " "
127
- , goldenTest " RecordCon.hs" 7 8 Auto " "
128
- , goldenTest " FmapJoin.hs" 2 14 Auto " "
129
- , goldenTest " Fgmap.hs" 2 9 Auto " "
130
- , goldenTest " FmapJoinInLet.hs" 4 19 Auto " "
107
+ $ autoTest " GoldenApplicativeThen.hs" 2 11
108
+ , autoTest " GoldenSafeHead.hs" 2 12
109
+ , expectFail " GoldenFish.hs"
110
+ 5 18 Auto " "
111
+ , autoTest " GoldenArbitrary.hs" 25 13
112
+ , autoTest " FmapBoth.hs" 2 12
113
+ , autoTest " RecordCon.hs" 7 8
114
+ , autoTest " FmapJoin.hs" 2 14
115
+ , autoTest " Fgmap.hs" 2 9
116
+ , autoTest " FmapJoinInLet.hs" 4 19
131
117
]
132
118
133
119
120
+ spec :: Spec
121
+ spec = do
122
+ it " GoldenTests" $
123
+ defaultMainWithIngredients
124
+ [antXMLRunner, rerunningTests [listingTests, consoleTestReporter]]
125
+ tests
126
+
127
+
128
+ ------------------------------------------------------------------------------
129
+ -- | Get a range at the given line and column corresponding to having nothing
130
+ -- selected.
131
+ --
132
+ -- NB: These coordinates are in "file space", ie, 1-indexed.
133
+ pointRange :: Int -> Int -> Range
134
+ pointRange
135
+ (subtract 1 -> line)
136
+ (subtract 1 -> col) =
137
+ Range (Position line col) (Position line $ col + 1 )
138
+
139
+
140
+ ------------------------------------------------------------------------------
141
+ -- | Get the title of a code action.
142
+ codeActionTitle :: (Command |? CodeAction ) -> Maybe Text
143
+ codeActionTitle InL {} = Nothing
144
+ codeActionTitle (InR (CodeAction title _ _ _ _ _ _)) = Just title
145
+
146
+
134
147
------------------------------------------------------------------------------
135
148
-- | Make a tactic unit test.
136
149
mkTest
@@ -146,7 +159,7 @@ mkTest
146
159
-> TestTree
147
160
mkTest name fp line col ts =
148
161
testCase name $ do
149
- runSession hlsCommand fullCaps tacticPath $ do
162
+ runSession testCommand fullCaps tacticPath $ do
150
163
doc <- openDoc fp " haskell"
151
164
_ <- waitForDiagnostics
152
165
actions <- getCodeActions doc $ pointRange line col
@@ -158,6 +171,10 @@ mkTest name fp line col ts =
158
171
@? (" Expected a code action with title " <> T. unpack title)
159
172
160
173
174
+ autoTest :: FilePath -> Int -> Int -> TestTree
175
+ autoTest fp line col = goldenTest fp line col Auto " "
176
+
177
+
161
178
setFeatureSet :: FeatureSet -> Session ()
162
179
setFeatureSet features = do
163
180
let unObject (Object obj) = obj
@@ -174,13 +191,15 @@ setFeatureSet features = do
174
191
DidChangeConfigurationParams $
175
192
toJSON config
176
193
194
+
177
195
goldenTest :: FilePath -> Int -> Int -> TacticCommand -> Text -> TestTree
178
196
goldenTest = goldenTest' allFeatures
179
197
198
+
180
199
goldenTest' :: FeatureSet -> FilePath -> Int -> Int -> TacticCommand -> Text -> TestTree
181
200
goldenTest' features input line col tc occ =
182
201
testCase (input <> " (golden)" ) $ do
183
- runSession hlsCommand fullCaps tacticPath $ do
202
+ runSession testCommand fullCaps tacticPath $ do
184
203
setFeatureSet features
185
204
doc <- openDoc input " haskell"
186
205
_ <- waitForDiagnostics
@@ -201,7 +220,7 @@ goldenTest' features input line col tc occ =
201
220
expectFail :: FilePath -> Int -> Int -> TacticCommand -> Text -> TestTree
202
221
expectFail input line col tc occ =
203
222
testCase (input <> " (golden)" ) $ do
204
- runSession hlsCommand fullCaps tacticPath $ do
223
+ runSession testCommand fullCaps tacticPath $ do
205
224
doc <- openDoc input " haskell"
206
225
_ <- waitForDiagnostics
207
226
actions <- getCodeActions doc $ pointRange line col
@@ -213,11 +232,16 @@ expectFail input line col tc occ =
213
232
214
233
215
234
tacticPath :: FilePath
216
- tacticPath = " test/testdata/tactic"
235
+ tacticPath = " test/golden"
236
+
217
237
238
+ testCommand :: String
239
+ testCommand = " test-server"
218
240
219
- executeCommandWithResp :: Command -> Session (ResponseMessage WorkspaceExecuteCommand )
241
+
242
+ executeCommandWithResp :: Command -> Session (ResponseMessage 'WorkspaceExecuteCommand)
220
243
executeCommandWithResp cmd = do
221
244
let args = decode $ encode $ fromJust $ cmd ^. arguments
222
245
execParams = ExecuteCommandParams Nothing (cmd ^. command) args
223
246
request SWorkspaceExecuteCommand execParams
247
+
0 commit comments