1
1
2
2
module ExceptionTests (tests ) where
3
3
4
- import Control.Concurrent.Async
5
4
import Control.Exception (ArithException (DivideByZero ),
6
- finally , throwIO )
5
+ throwIO )
7
6
import Control.Lens
8
7
import Control.Monad.Error.Class (MonadError (throwError ))
9
8
import Control.Monad.IO.Class (liftIO )
@@ -12,6 +11,7 @@ import Data.Text as T
12
11
import Development.IDE.Core.Shake (IdeState (.. ))
13
12
import qualified Development.IDE.LSP.Notifications as Notifications
14
13
import qualified Development.IDE.Main as IDE
14
+ import Development.IDE.Plugin.HLS (toResponseError )
15
15
import Development.IDE.Plugin.Test as Test
16
16
import Development.IDE.Types.Options
17
17
import GHC.Base (coerce )
@@ -30,8 +30,6 @@ import Language.LSP.Protocol.Types hiding
30
30
mkRange )
31
31
import Language.LSP.Test
32
32
import LogType (Log (.. ))
33
- import System.Directory
34
- import System.Process.Extra (createPipe )
35
33
import Test.Tasty
36
34
import Test.Tasty.HUnit
37
35
import TestUtils
@@ -50,7 +48,6 @@ tests recorder logger = do
50
48
pure (InL [] )
51
49
]
52
50
}]
53
-
54
51
testIde recorder (testingLite recorder logger plugins) $ do
55
52
doc <- createDoc " A.hs" " haskell" " module A where"
56
53
waitForProgressDone
@@ -60,6 +57,7 @@ tests recorder logger = do
60
57
liftIO $ assertBool " We caught an error, but it wasn't ours!"
61
58
(T. isInfixOf " divide by zero" _message && T. isInfixOf (coerce pluginId) _message)
62
59
_ -> liftIO $ assertFailure $ show lens
60
+
63
61
, testCase " Commands" $ do
64
62
let pluginId = " command-exception"
65
63
commandId = CommandId " exception"
@@ -71,7 +69,6 @@ tests recorder logger = do
71
69
pure (InR Null )
72
70
]
73
71
}]
74
-
75
72
testIde recorder (testingLite recorder logger plugins) $ do
76
73
_ <- createDoc " A.hs" " haskell" " module A where"
77
74
waitForProgressDone
@@ -83,6 +80,7 @@ tests recorder logger = do
83
80
liftIO $ assertBool " We caught an error, but it wasn't ours!"
84
81
(T. isInfixOf " divide by zero" _message && T. isInfixOf (coerce pluginId) _message)
85
82
_ -> liftIO $ assertFailure $ show res
83
+
86
84
, testCase " Notification Handlers" $ do
87
85
let pluginId = " notification-exception"
88
86
plugins = pluginDescToIdePlugins $
@@ -95,101 +93,24 @@ tests recorder logger = do
95
93
[ mkPluginHandler SMethod_TextDocumentCodeLens $ \ _ _ _-> do
96
94
pure (InL [] )
97
95
]
98
- }
99
- , Notifications. descriptor (cmapWithPrio LogNotifications recorder) " ghcide-core" ]
100
-
96
+ }]
101
97
testIde recorder (testingLite recorder logger plugins) $ do
102
98
doc <- createDoc " A.hs" " haskell" " module A where"
103
99
waitForProgressDone
104
100
(view L. result -> lens) <- request SMethod_TextDocumentCodeLens (CodeLensParams Nothing Nothing doc)
105
101
case lens of
106
102
Right (InL [] ) ->
103
+ -- We don't get error responses from notification handlers, so
104
+ -- we can only make sure that the server is still responding
107
105
pure ()
108
106
_ -> liftIO $ assertFailure $ " We should have had an empty list" <> show lens]
109
107
110
108
, testGroup " Testing PluginError order..."
111
- [ testCase " InternalError over InvalidParams" $ do
112
- let pluginId = " internal-error-order"
113
- plugins = pluginDescToIdePlugins $
114
- [ (defaultPluginDescriptor pluginId)
115
- { pluginHandlers = mconcat
116
- [ mkPluginHandler SMethod_TextDocumentCodeLens $ \ _ _ _-> do
117
- throwError $ PluginInternalError " error test"
118
- ,mkPluginHandler SMethod_TextDocumentCodeLens $ \ _ _ _-> do
119
- throwError $ PluginInvalidParams " error test"
120
- ]
121
- }
122
- , Notifications. descriptor (cmapWithPrio LogNotifications recorder) " ghcide-core" ]
123
-
124
- testIde recorder (testingLite recorder logger plugins) $ do
125
- doc <- createDoc " A.hs" " haskell" " module A where"
126
- waitForProgressDone
127
- (view L. result -> lens) <- request SMethod_TextDocumentCodeLens (CodeLensParams Nothing Nothing doc)
128
- case lens of
129
- Left (ResponseError {_code = InR ErrorCodes_InternalError , _message}) ->
130
- liftIO $ assertBool " We caught an error, but it wasn't ours!"
131
- (T. isInfixOf " error test" _message && T. isInfixOf (coerce pluginId) _message)
132
- _ -> liftIO $ assertFailure $ show lens
133
- , testCase " InvalidParams over InvalidUserState" $ do
134
- let pluginId = " invalid-params-order"
135
- plugins = pluginDescToIdePlugins $
136
- [ (defaultPluginDescriptor pluginId)
137
- { pluginHandlers = mconcat
138
- [ mkPluginHandler SMethod_TextDocumentCodeLens $ \ _ _ _-> do
139
- throwError $ PluginInvalidParams " error test"
140
- ,mkPluginHandler SMethod_TextDocumentCodeLens $ \ _ _ _-> do
141
- throwError $ PluginInvalidUserState " error test"
142
- ]
143
- }
144
- , Notifications. descriptor (cmapWithPrio LogNotifications recorder) " ghcide-core" ]
145
-
146
- testIde recorder (testingLite recorder logger plugins) $ do
147
- doc <- createDoc " A.hs" " haskell" " module A where"
148
- waitForProgressDone
149
- (view L. result -> lens) <- request SMethod_TextDocumentCodeLens (CodeLensParams Nothing Nothing doc)
150
- case lens of
151
- Left (ResponseError {_code = InR ErrorCodes_InvalidParams , _message}) ->
152
- liftIO $ assertBool " We caught an error, but it wasn't ours!"
153
- (T. isInfixOf " error test" _message && T. isInfixOf (coerce pluginId) _message)
154
- _ -> liftIO $ assertFailure $ show lens
155
- , testCase " InvalidUserState over RequestRefused" $ do
156
- let pluginId = " invalid-user-state-order"
157
- plugins = pluginDescToIdePlugins $
158
- [ (defaultPluginDescriptor pluginId)
159
- { pluginHandlers = mconcat
160
- [ mkPluginHandler SMethod_TextDocumentCodeLens $ \ _ _ _-> do
161
- throwError $ PluginInvalidUserState " error test"
162
- ,mkPluginHandler SMethod_TextDocumentCodeLens $ \ _ _ _-> do
163
- throwError $ PluginRequestRefused " error test"
164
- ]
165
- }
166
- , Notifications. descriptor (cmapWithPrio LogNotifications recorder) " ghcide-core" ]
167
-
168
- testIde recorder (testingLite recorder logger plugins) $ do
169
- doc <- createDoc " A.hs" " haskell" " module A where"
170
- waitForProgressDone
171
- (view L. result -> lens) <- request SMethod_TextDocumentCodeLens (CodeLensParams Nothing Nothing doc)
172
- case lens of
173
- Left (ResponseError {_code = InL LSPErrorCodes_RequestFailed , _message}) ->
174
- liftIO $ assertBool " We caught an error, but it wasn't ours!"
175
- (T. isInfixOf " error test" _message && T. isInfixOf (coerce pluginId) _message)
176
- _ -> liftIO $ assertFailure $ show lens
177
- ]]
178
-
179
- testIde :: Recorder (WithPriority Log ) -> IDE. Arguments -> Session () -> IO ()
180
- testIde recorder arguments session = do
181
- config <- getConfigFromEnv
182
- cwd <- getCurrentDirectory
183
- (hInRead, hInWrite) <- createPipe
184
- (hOutRead, hOutWrite) <- createPipe
185
- let projDir = " ."
186
- let server = IDE. defaultMain (cmapWithPrio LogIDEMain recorder) arguments
187
- { IDE. argsHandleIn = pure hInRead
188
- , IDE. argsHandleOut = pure hOutWrite
189
- }
190
-
191
- flip finally (setCurrentDirectory cwd) $ withAsync server $ \ _ ->
192
- runSessionWithHandles hInWrite hOutRead config lspTestCaps projDir session
109
+ [ pluginOrderTestCase recorder logger " InternalError over InvalidParams" PluginInternalError PluginInvalidParams
110
+ , pluginOrderTestCase recorder logger " InvalidParams over InvalidUserState" PluginInvalidParams PluginInvalidUserState
111
+ , pluginOrderTestCase recorder logger " InvalidUserState over RequestRefused" PluginInvalidUserState PluginRequestRefused
112
+ ]
113
+ ]
193
114
194
115
testingLite :: Recorder (WithPriority Log ) -> Logger -> IdePlugins IdeState -> IDE. Arguments
195
116
testingLite recorder logger plugins =
@@ -210,3 +131,25 @@ testingLite recorder logger plugins =
210
131
{ IDE. argsHlsPlugins = hlsPlugins
211
132
, IDE. argsIdeOptions = ideOptions
212
133
}
134
+
135
+ pluginOrderTestCase :: Recorder (WithPriority Log ) -> Logger -> TestName -> (T. Text -> PluginError ) -> (T. Text -> PluginError ) -> TestTree
136
+ pluginOrderTestCase recorder logger msg err1 err2 =
137
+ testCase msg $ do
138
+ let pluginId = " error-order-test"
139
+ plugins = pluginDescToIdePlugins $
140
+ [ (defaultPluginDescriptor pluginId)
141
+ { pluginHandlers = mconcat
142
+ [ mkPluginHandler SMethod_TextDocumentCodeLens $ \ _ _ _-> do
143
+ throwError $ err1 " error test"
144
+ ,mkPluginHandler SMethod_TextDocumentCodeLens $ \ _ _ _-> do
145
+ throwError $ err2 " error test"
146
+ ]
147
+ }]
148
+ testIde recorder (testingLite recorder logger plugins) $ do
149
+ doc <- createDoc " A.hs" " haskell" " module A where"
150
+ waitForProgressDone
151
+ (view L. result -> lens) <- request SMethod_TextDocumentCodeLens (CodeLensParams Nothing Nothing doc)
152
+ case lens of
153
+ Left re | toResponseError (pluginId, err1 " error test" ) == re -> pure ()
154
+ | otherwise -> liftIO $ assertFailure " We caught an error, but it wasn't ours!"
155
+ _ -> liftIO $ assertFailure $ show lens
0 commit comments