@@ -2890,17 +2890,21 @@ removeRedundantConstraintsTests = let
2890
2890
2891
2891
addSigActionTests :: TestTree
2892
2892
addSigActionTests = let
2893
- header = " {-# OPTIONS_GHC -Wmissing-signatures -Wmissing-pattern-synonym-signatures #-}"
2894
- moduleH = " {-# LANGUAGE PatternSynonyms #-}\n module Sigs where"
2895
- before def = T. unlines [header, moduleH, def]
2896
- after' def sig = T. unlines [header, moduleH, sig, def]
2897
-
2898
- def >:: sig = testSession (T. unpack def) $ do
2893
+ header = [ " {-# OPTIONS_GHC -Wmissing-signatures -Wmissing-pattern-synonym-signatures #-}"
2894
+ , " {-# LANGUAGE PatternSynonyms,BangPatterns,GADTs #-}"
2895
+ , " module Sigs where"
2896
+ , " data T1 a where"
2897
+ , " MkT1 :: (Show b) => a -> b -> T1 a"
2898
+ ]
2899
+ before def = T. unlines $ header ++ [def]
2900
+ after' def sig = T. unlines $ header ++ [sig, def]
2901
+
2902
+ def >:: sig = testSession (T. unpack $ T. replace " \n " " \\ n" def) $ do
2899
2903
let originalCode = before def
2900
2904
let expectedCode = after' def sig
2901
2905
doc <- createDoc " Sigs.hs" " haskell" originalCode
2902
2906
_ <- waitForDiagnostics
2903
- actionsOrCommands <- getCodeActions doc (Range (Position 3 1 ) (Position 3 maxBound ))
2907
+ actionsOrCommands <- getCodeActions doc (Range (Position 5 1 ) (Position 5 maxBound ))
2904
2908
chosenAction <- liftIO $ pickActionWithTitle (" add signature: " <> sig) actionsOrCommands
2905
2909
executeCodeAction chosenAction
2906
2910
modifiedCode <- documentContents doc
@@ -2914,6 +2918,15 @@ addSigActionTests = let
2914
2918
, " a >>>> b = a + b" >:: " (>>>>) :: Num a => a -> a -> a"
2915
2919
, " a `haha` b = a b" >:: " haha :: (t1 -> t2) -> t1 -> t2"
2916
2920
, " pattern Some a = Just a" >:: " pattern Some :: a -> Maybe a"
2921
+ , " pattern Some a <- Just a" >:: " pattern Some :: a -> Maybe a"
2922
+ , " pattern Some a <- Just a\n where Some a = Just a" >:: " pattern Some :: a -> Maybe a"
2923
+ , " pattern Some a <- Just !a\n where Some !a = Just a" >:: " pattern Some :: a -> Maybe a"
2924
+ , " pattern Point{x, y} = (x, y)" >:: " pattern Point :: a -> b -> (a, b)"
2925
+ , " pattern Point{x, y} <- (x, y)" >:: " pattern Point :: a -> b -> (a, b)"
2926
+ , " pattern Point{x, y} <- (x, y)\n where Point x y = (x, y)" >:: " pattern Point :: a -> b -> (a, b)"
2927
+ , " pattern MkT1' b = MkT1 42 b" >:: " pattern MkT1' :: (Eq a, Num a) => Show b => b -> T1 a"
2928
+ , " pattern MkT1' b <- MkT1 42 b" >:: " pattern MkT1' :: (Eq a, Num a) => Show b => b -> T1 a"
2929
+ , " pattern MkT1' b <- MkT1 42 b\n where MkT1' b = T1 42 b" >:: " pattern MkT1' :: (Eq a, Num a) => Show b => b -> T1 a"
2917
2930
]
2918
2931
2919
2932
exportUnusedTests :: TestTree
@@ -3377,10 +3390,12 @@ addSigLensesTests =
3377
3390
let pragmas = " {-# OPTIONS_GHC -Wmissing-signatures -Wmissing-pattern-synonym-signatures #-}"
3378
3391
moduleH exported =
3379
3392
T. unlines
3380
- [ " {-# LANGUAGE PatternSynonyms,TypeApplications,DataKinds,RankNTypes,ScopedTypeVariables,TypeOperators #-}"
3393
+ [ " {-# LANGUAGE PatternSynonyms,TypeApplications,DataKinds,RankNTypes,ScopedTypeVariables,TypeOperators,GADTs,BangPatterns #-}"
3381
3394
, " module Sigs(" <> exported <> " ) where"
3382
3395
, " import qualified Data.Complex as C"
3383
3396
, " import Data.Data (Proxy (..), type (:~:) (..), mkCharType)"
3397
+ , " data T1 a where"
3398
+ , " MkT1 :: (Show b) => a -> b -> T1 a"
3384
3399
]
3385
3400
before enableGHCWarnings exported (def, _) others =
3386
3401
T. unlines $ [pragmas | enableGHCWarnings] <> [moduleH exported, def] <> others
@@ -3409,6 +3424,15 @@ addSigLensesTests =
3409
3424
, (" a >>>> b = a + b" , " (>>>>) :: Num a => a -> a -> a" )
3410
3425
, (" a `haha` b = a b" , " haha :: (t1 -> t2) -> t1 -> t2" )
3411
3426
, (" pattern Some a = Just a" , " pattern Some :: a -> Maybe a" )
3427
+ , (" pattern Some a <- Just a" , " pattern Some :: a -> Maybe a" )
3428
+ , (" pattern Some a <- Just a\n where Some a = Just a" , " pattern Some :: a -> Maybe a" )
3429
+ , (" pattern Some a <- Just !a\n where Some !a = Just a" , " pattern Some :: a -> Maybe a" )
3430
+ , (" pattern Point{x, y} = (x, y)" , " pattern Point :: a -> b -> (a, b)" )
3431
+ , (" pattern Point{x, y} <- (x, y)" , " pattern Point :: a -> b -> (a, b)" )
3432
+ , (" pattern Point{x, y} <- (x, y)\n where Point x y = (x, y)" , " pattern Point :: a -> b -> (a, b)" )
3433
+ , (" pattern MkT1' b = MkT1 42 b" , " pattern MkT1' :: (Eq a, Num a) => Show b => b -> T1 a" )
3434
+ , (" pattern MkT1' b <- MkT1 42 b" , " pattern MkT1' :: (Eq a, Num a) => Show b => b -> T1 a" )
3435
+ , (" pattern MkT1' b <- MkT1 42 b\n where MkT1' b = T1 42 b" , " pattern MkT1' :: (Eq a, Num a) => Show b => b -> T1 a" )
3412
3436
, (" qualifiedSigTest= C.realPart" , " qualifiedSigTest :: C.Complex a -> a" )
3413
3437
, (" head = 233" , " head :: Integer" )
3414
3438
, (" rank2Test (k :: forall a . a -> a) = (k 233 :: Int, k \" QAQ\" )" , " rank2Test :: (forall a. a -> a) -> (Int, " <> listOfChar <> " )" )
@@ -3419,7 +3443,7 @@ addSigLensesTests =
3419
3443
]
3420
3444
in testGroup
3421
3445
" add signature"
3422
- [ testGroup " signatures are correct" [sigSession (T. unpack def) False " always" " " (def, Just sig) [] | (def, sig) <- cases]
3446
+ [ testGroup " signatures are correct" [sigSession (T. unpack $ T. replace " \n " " \\ n " def) False " always" " " (def, Just sig) [] | (def, sig) <- cases]
3423
3447
, sigSession " exported mode works" False " exported" " xyz" (" xyz = True" , Just " xyz :: Bool" ) (fst <$> take 3 cases)
3424
3448
, testGroup
3425
3449
" diagnostics mode works"
0 commit comments