1
+ {-# LANGUAGE DataKinds #-}
1
2
{-# LANGUAGE QuasiQuotes #-}
2
3
4
+ import Control.Arrow ((>>>) )
3
5
import Control.Exception (throw )
4
6
import Control.Lens ((^.) )
5
7
import Data.Maybe (fromJust )
@@ -201,7 +203,9 @@ main =
201
203
[ Nothing ,
202
204
Just $ SimilarSignatureHelp $ SignatureHelp [SignatureInformation " f :: forall abcdefghijklmn. Num abcdefghijklmn => abcdefghijklmn -> abcdefghijklmn -> abcdefghijklmn -> abcdefghijklmn -> abcdefghijklmn" Nothing (Just [ParameterInformation (InR (50 ,64 )) Nothing , ParameterInformation (InR (68 ,82 )) Nothing , ParameterInformation (InR (86 ,100 )) Nothing , ParameterInformation (InR (104 ,118 )) Nothing ]) (Just (InL 0 )), SignatureInformation " f :: Integer -> Integer -> Integer -> Integer -> Integer" Nothing (Just [ParameterInformation (InR (5 ,12 )) Nothing , ParameterInformation (InR (16 ,23 )) Nothing , ParameterInformation (InR (27 ,34 )) Nothing , ParameterInformation (InR (38 ,45 )) Nothing ]) (Just (InL 0 ))] (Just 0 ) (Just (InL 0 ))
203
205
],
204
- mkTest
206
+ -- TODO fix bug of wrong arg range in the function type string
207
+ -- https://github.com/haskell/haskell-language-server/pull/4626#discussion_r2261133076
208
+ mkTestExpectFail
205
209
" middle =>"
206
210
[__i |
207
211
f :: Eq a => a -> Num b => b -> b
@@ -213,12 +217,22 @@ main =
213
217
z = f 1
214
218
^
215
219
|]
216
- [ Nothing ,
217
- Just $ SimilarSignatureHelp $ SignatureHelp [SignatureInformation " f :: forall a b. Eq a => a -> Num b => b -> b" Nothing (Just [ParameterInformation (InR (25 ,26 )) Nothing , ParameterInformation (InR (39 ,40 )) Nothing ]) (Just (InL 0 )), SignatureInformation " f :: Integer -> Num Bool => Bool -> Bool" Nothing (Just [ParameterInformation (InR (5 ,12 )) Nothing , ParameterInformation (InR (28 ,32 )) Nothing ]) (Just (InL 0 ))] (Just 0 ) (Just (InL 0 )),
218
- Just $ SimilarSignatureHelp $ SignatureHelp [SignatureInformation " f :: forall a b. Eq a => a -> Num b => b -> b" Nothing (Just [ParameterInformation (InR (25 ,26 )) Nothing , ParameterInformation (InR (39 ,40 )) Nothing ]) (Just (InL 1 )), SignatureInformation " f :: Integer -> Num Bool => Bool -> Bool" Nothing (Just [ParameterInformation (InR (5 ,12 )) Nothing , ParameterInformation (InR (28 ,32 )) Nothing ]) (Just (InL 1 ))] (Just 0 ) (Just (InL 1 )),
219
- Just $ SimilarSignatureHelp $ SignatureHelp [SignatureInformation " f :: forall a b. Eq a => a -> Num b => b -> b" Nothing (Just [ParameterInformation (InR (25 ,26 )) Nothing , ParameterInformation (InR (39 ,40 )) Nothing ]) (Just (InL 0 )), SignatureInformation " f :: Bool -> Num Integer => Integer -> Integer" Nothing (Just [ParameterInformation (InR (5 ,9 )) Nothing , ParameterInformation (InR (28 ,35 )) Nothing ]) (Just (InL 0 ))] (Just 0 ) (Just (InL 0 )),
220
- Just $ SimilarSignatureHelp $ SignatureHelp [SignatureInformation " f :: forall a b. Eq a => a -> Num b => b -> b" Nothing (Just [ParameterInformation (InR (25 ,26 )) Nothing , ParameterInformation (InR (39 ,40 )) Nothing ]) (Just (InL 0 )), SignatureInformation " f :: Integer -> Num Integer => Integer -> Integer" Nothing (Just [ParameterInformation (InR (5 ,12 )) Nothing , ParameterInformation (InR (31 ,38 )) Nothing ]) (Just (InL 0 ))] (Just 0 ) (Just (InL 0 ))
221
- ],
220
+ ( BrokenIdeal
221
+ [ Nothing ,
222
+ Just $ SimilarSignatureHelp $ SignatureHelp [SignatureInformation " f :: forall a b. Eq a => a -> Num b => b -> b" Nothing (Just [ParameterInformation (InR (25 ,26 )) Nothing , ParameterInformation (InR (39 ,40 )) Nothing ]) (Just (InL 0 )), SignatureInformation " f :: Integer -> Num Bool => Bool -> Bool" Nothing (Just [ParameterInformation (InR (5 ,12 )) Nothing , ParameterInformation (InR (28 ,32 )) Nothing ]) (Just (InL 0 ))] (Just 0 ) (Just (InL 0 )),
223
+ Just $ SimilarSignatureHelp $ SignatureHelp [SignatureInformation " f :: forall a b. Eq a => a -> Num b => b -> b" Nothing (Just [ParameterInformation (InR (25 ,26 )) Nothing , ParameterInformation (InR (39 ,40 )) Nothing ]) (Just (InL 1 )), SignatureInformation " f :: Integer -> Num Bool => Bool -> Bool" Nothing (Just [ParameterInformation (InR (5 ,12 )) Nothing , ParameterInformation (InR (28 ,32 )) Nothing ]) (Just (InL 1 ))] (Just 0 ) (Just (InL 1 )),
224
+ Just $ SimilarSignatureHelp $ SignatureHelp [SignatureInformation " f :: forall a b. Eq a => a -> Num b => b -> b" Nothing (Just [ParameterInformation (InR (25 ,26 )) Nothing , ParameterInformation (InR (39 ,40 )) Nothing ]) (Just (InL 0 )), SignatureInformation " f :: Bool -> Num Integer => Integer -> Integer" Nothing (Just [ParameterInformation (InR (5 ,9 )) Nothing , ParameterInformation (InR (28 ,35 )) Nothing ]) (Just (InL 0 ))] (Just 0 ) (Just (InL 0 )),
225
+ Just $ SimilarSignatureHelp $ SignatureHelp [SignatureInformation " f :: forall a b. Eq a => a -> Num b => b -> b" Nothing (Just [ParameterInformation (InR (25 ,26 )) Nothing , ParameterInformation (InR (39 ,40 )) Nothing ]) (Just (InL 0 )), SignatureInformation " f :: Integer -> Num Integer => Integer -> Integer" Nothing (Just [ParameterInformation (InR (5 ,12 )) Nothing , ParameterInformation (InR (31 ,38 )) Nothing ]) (Just (InL 0 ))] (Just 0 ) (Just (InL 0 ))
226
+ ]
227
+ )
228
+ ( BrokenCurrent
229
+ [ Nothing ,
230
+ Just $ SimilarSignatureHelp $ SignatureHelp [SignatureInformation " f :: forall a b. Eq a => a -> Num b => b -> b" Nothing (Just [ParameterInformation (InR (25 ,26 )) Nothing , ParameterInformation (InR (39 ,40 )) Nothing ]) (Just (InL 0 )), SignatureInformation " f :: Integer -> Num Bool => Bool -> Bool" Nothing (Just [ParameterInformation (InR (5 ,12 )) Nothing , ParameterInformation (InR (28 ,32 )) Nothing ]) (Just (InL 0 ))] (Just 0 ) (Just (InL 0 )),
231
+ Just $ SimilarSignatureHelp $ SignatureHelp [SignatureInformation " f :: forall a b. Eq a => a -> Num b => b -> b" Nothing (Just [ParameterInformation (InR (25 ,26 )) Nothing , ParameterInformation (InR (39 ,40 )) Nothing ]) (Just (InL 1 )), SignatureInformation " f :: Integer -> Num Bool => Bool -> Bool" Nothing (Just [ParameterInformation (InR (5 ,12 )) Nothing , ParameterInformation (InR (28 ,32 )) Nothing ]) (Just (InL 1 ))] (Just 0 ) (Just (InL 1 )),
232
+ Just $ SimilarSignatureHelp $ SignatureHelp [SignatureInformation " f :: forall a b. Eq a => a -> Num b => b -> b" Nothing (Just [ParameterInformation (InR (25 ,26 )) Nothing , ParameterInformation (InR (39 ,40 )) Nothing ]) (Just (InL 0 )), SignatureInformation " f :: Bool -> Num Integer => Integer -> Integer" Nothing (Just [ParameterInformation (InR (5 ,9 )) Nothing , ParameterInformation (InR (28 ,35 )) Nothing ]) (Just (InL 0 ))] (Just 0 ) (Just (InL 0 )),
233
+ Just $ SimilarSignatureHelp $ SignatureHelp [SignatureInformation " f :: forall a b. Eq a => a -> Num b => b -> b" Nothing (Just [ParameterInformation (InR (25 ,26 )) Nothing , ParameterInformation (InR (39 ,40 )) Nothing ]) (Just (InL 0 )), SignatureInformation " f :: Integer -> Num Integer => Integer -> Integer" Nothing (Just [ParameterInformation (InR (20 ,27 )) Nothing , ParameterInformation (InR (31 ,38 )) Nothing ]) (Just (InL 0 ))] (Just 0 ) (Just (InL 0 ))
234
+ ]
235
+ ),
222
236
mkTest
223
237
" => in argument"
224
238
[__i |
@@ -257,28 +271,46 @@ main =
257
271
Just $ SimilarSignatureHelp $ SignatureHelp [SignatureInformation " f :: forall a. Maybe a -> forall b. (a, b) -> b" Nothing (Just [ParameterInformation (InR (15 ,22 )) Nothing , ParameterInformation (InR (36 ,42 )) Nothing ]) (Just (InL 0 )), SignatureInformation " f :: Maybe Bool -> forall b. (Bool, b) -> b" Nothing (Just [ParameterInformation (InR (5 ,15 )) Nothing , ParameterInformation (InR (29 ,38 )) Nothing ]) (Just (InL 0 ))] (Just 0 ) (Just (InL 0 )),
258
272
Just $ SimilarSignatureHelp $ SignatureHelp [SignatureInformation " f :: forall a. Maybe a -> forall b. (a, b) -> b" Nothing (Just [ParameterInformation (InR (15 ,22 )) Nothing , ParameterInformation (InR (36 ,42 )) Nothing ]) (Just (InL 0 )), SignatureInformation " f :: Maybe Integer -> forall b. (Integer, b) -> b" Nothing (Just [ParameterInformation (InR (5 ,18 )) Nothing , ParameterInformation (InR (32 ,44 )) Nothing ]) (Just (InL 0 ))] (Just 0 ) (Just (InL 0 ))
259
273
],
260
- mkTest
274
+ -- TODO fix bug of wrong arg range in the function type string
275
+ -- https://github.com/haskell/haskell-language-server/pull/4626#discussion_r2261133076
276
+ mkTestExpectFail
261
277
" RankNTypes(forall in middle), another"
262
278
[__i |
263
279
f :: l -> forall a. a -> a
264
280
f = _
265
281
x = f 1
266
282
^ ^
267
283
|]
268
- [ Nothing ,
269
- Just $ SimilarSignatureHelp $ SignatureHelp [SignatureInformation " f :: forall l. l -> forall a. a -> a" Nothing (Just [ParameterInformation (InR (15 ,16 )) Nothing , ParameterInformation (InR (30 ,31 )) Nothing ]) (Just (InL 0 )), SignatureInformation " f :: Integer -> forall a. a -> a" Nothing (Just [ParameterInformation (InR (5 ,12 )) Nothing , ParameterInformation (InR (26 ,27 )) Nothing ]) (Just (InL 0 ))] (Just 0 ) (Just (InL 0 ))
270
- ],
271
- mkTest
284
+ ( BrokenIdeal
285
+ [ Nothing ,
286
+ Just $ SimilarSignatureHelp $ SignatureHelp [SignatureInformation " f :: forall l. l -> forall a. a -> a" Nothing (Just [ParameterInformation (InR (15 ,16 )) Nothing , ParameterInformation (InR (30 ,31 )) Nothing ]) (Just (InL 0 )), SignatureInformation " f :: Integer -> forall a. a -> a" Nothing (Just [ParameterInformation (InR (5 ,12 )) Nothing , ParameterInformation (InR (26 ,27 )) Nothing ]) (Just (InL 0 ))] (Just 0 ) (Just (InL 0 ))
287
+ ]
288
+ )
289
+ ( BrokenCurrent
290
+ [ Nothing ,
291
+ Just $ SimilarSignatureHelp $ SignatureHelp [SignatureInformation " f :: forall l. l -> forall a. a -> a" Nothing (Just [ParameterInformation (InR (25 ,26 )) Nothing , ParameterInformation (InR (30 ,31 )) Nothing ]) (Just (InL 0 )), SignatureInformation " f :: Integer -> forall a. a -> a" Nothing (Just [ParameterInformation (InR (5 ,12 )) Nothing , ParameterInformation (InR (26 ,27 )) Nothing ]) (Just (InL 0 ))] (Just 0 ) (Just (InL 0 ))
292
+ ]
293
+ ),
294
+ -- TODO fix bug of wrong arg range in the function type string
295
+ -- https://github.com/haskell/haskell-language-server/pull/4626#discussion_r2261133076
296
+ mkTestExpectFail
272
297
" RankNTypes(forall in middle), again"
273
298
[__i |
274
299
f :: a -> forall a. a -> a
275
300
f = _
276
301
x = f 1
277
302
^ ^
278
303
|]
279
- [ Nothing ,
280
- Just $ SimilarSignatureHelp $ SignatureHelp [SignatureInformation " f :: forall a. a -> forall a1. a1 -> a1" Nothing (Just [ParameterInformation (InR (15 ,16 )) Nothing , ParameterInformation (InR (31 ,33 )) Nothing ]) (Just (InL 0 )), SignatureInformation " f :: Integer -> forall a. a -> a" Nothing (Just [ParameterInformation (InR (5 ,12 )) Nothing , ParameterInformation (InR (26 ,27 )) Nothing ]) (Just (InL 0 ))] (Just 0 ) (Just (InL 0 ))
281
- ],
304
+ ( BrokenIdeal
305
+ [ Nothing ,
306
+ Just $ SimilarSignatureHelp $ SignatureHelp [SignatureInformation " f :: forall a. a -> forall a1. a1 -> a1" Nothing (Just [ParameterInformation (InR (15 ,16 )) Nothing , ParameterInformation (InR (31 ,33 )) Nothing ]) (Just (InL 0 )), SignatureInformation " f :: Integer -> forall a. a -> a" Nothing (Just [ParameterInformation (InR (5 ,12 )) Nothing , ParameterInformation (InR (26 ,27 )) Nothing ]) (Just (InL 0 ))] (Just 0 ) (Just (InL 0 ))
307
+ ]
308
+ )
309
+ ( BrokenCurrent
310
+ [ Nothing ,
311
+ Just $ SimilarSignatureHelp $ SignatureHelp [SignatureInformation " f :: forall a. a -> forall a1. a1 -> a1" Nothing (Just [ParameterInformation (InR (27 ,28 )) Nothing , ParameterInformation (InR (31 ,32 )) Nothing ]) (Just (InL 0 )), SignatureInformation " f :: Integer -> forall a. a -> a" Nothing (Just [ParameterInformation (InR (5 ,12 )) Nothing , ParameterInformation (InR (26 ,27 )) Nothing ]) (Just (InL 0 ))] (Just 0 ) (Just (InL 0 ))
312
+ ]
313
+ ),
282
314
mkTest
283
315
" LinearTypes"
284
316
[__i |
@@ -366,6 +398,14 @@ mkTest name sourceCode expectedSignatureHelps =
366
398
expectedSignatureHelps
367
399
getSignatureHelpFromSession
368
400
401
+ mkTestExpectFail ::
402
+ TestName ->
403
+ Text ->
404
+ ExpectBroken 'Ideal [Maybe SimilarSignatureHelp ] ->
405
+ ExpectBroken 'Current [Maybe SimilarSignatureHelp ] ->
406
+ TestTree
407
+ mkTestExpectFail name sourceCode _idealSignatureHelps = unCurrent >>> mkTest name sourceCode
408
+
369
409
getSignatureHelpFromSession :: Text -> PosPrefixInfo -> IO (Maybe SimilarSignatureHelp )
370
410
getSignatureHelpFromSession sourceCode (PosPrefixInfo _ _ _ position) =
371
411
let fileName = " A.hs"
0 commit comments