Skip to content

Commit 140cdcd

Browse files
isovectormergify[bot]
authored andcommitted
Don't suggest empty case lenses for case exprs with no data cons (#1962)
Co-authored-by: mergify[bot] <37929162+mergify[bot]@users.noreply.github.com>
1 parent 80ecf98 commit 140cdcd

File tree

4 files changed

+35
-8
lines changed

4 files changed

+35
-8
lines changed

plugins/hls-tactics-plugin/src/Wingman/EmptyCase.hs

Lines changed: 9 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -150,16 +150,19 @@ emptyCaseScrutinees state nfp = do
150150
hscenv <- stale GhcSessionDeps
151151

152152
let scrutinees = traverse (emptyCaseQ . tcg_binds) tcg
153-
for scrutinees $ \aged@(unTrack -> (ss, scrutinee)) -> do
153+
fmap catMaybes $ for scrutinees $ \aged@(unTrack -> (ss, scrutinee)) -> do
154154
ty <- MaybeT
155155
. fmap (scrutinzedType <=< sequence)
156156
. traverse (typeCheck (hscEnv $ untrackedStaleValue hscenv) tcg')
157157
$ scrutinee
158-
case ss of
159-
RealSrcSpan r -> do
160-
rss' <- liftMaybe $ mapAgeTo tcg_map $ unsafeCopyAge aged r
161-
pure (rss', ty)
162-
UnhelpfulSpan _ -> empty
158+
case null $ tacticsGetDataCons ty of
159+
True -> pure empty
160+
False ->
161+
case ss of
162+
RealSrcSpan r -> do
163+
rss' <- liftMaybe $ mapAgeTo tcg_map $ unsafeCopyAge aged r
164+
pure $ Just (rss', ty)
165+
UnhelpfulSpan _ -> empty
163166

164167
data EmptyCaseSort a
165168
= EmptyCase a

plugins/hls-tactics-plugin/test/CodeLens/EmptyCaseSpec.hs

Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -9,6 +9,7 @@ import Utils
99
spec :: Spec
1010
spec = do
1111
let test = mkCodeLensTest
12+
noTest = mkNoCodeLensTest
1213

1314
describe "golden" $ do
1415
test "EmptyCaseADT"
@@ -19,3 +20,6 @@ spec = do
1920
test "EmptyCaseGADT"
2021
test "EmptyCaseLamCase"
2122

23+
describe "no code lenses" $ do
24+
noTest "EmptyCaseSpuriousGADT"
25+

plugins/hls-tactics-plugin/test/Utils.hs

Lines changed: 14 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -15,12 +15,10 @@ import Control.Monad.IO.Class
1515
import Data.Aeson
1616
import Data.Foldable
1717
import Data.Function (on)
18-
import qualified Data.Map as M
1918
import Data.Maybe
2019
import Data.Text (Text)
2120
import qualified Data.Text as T
2221
import qualified Data.Text.IO as T
23-
import qualified Ide.Plugin.Config as Plugin
2422
import Ide.Plugin.Tactic as Tactic
2523
import Language.LSP.Types
2624
import Language.LSP.Types.Lens hiding (actions, applyEdit, capabilities, executeCommand, id, line, message, name, rename, title)
@@ -129,6 +127,20 @@ mkCodeLensTest input =
129127
liftIO $ edited `shouldBe` expected
130128

131129

130+
------------------------------------------------------------------------------
131+
-- | A test that no code lenses can be run in the file
132+
mkNoCodeLensTest
133+
:: FilePath
134+
-> SpecWith ()
135+
mkNoCodeLensTest input =
136+
it (input <> " (no code lenses)") $ do
137+
runSessionWithServer plugin tacticPath $ do
138+
doc <- openDoc (input <.> "hs") "haskell"
139+
_ <- waitForDiagnostics
140+
lenses <- fmap (reverse . filter isWingmanLens) $ getCodeLenses doc
141+
liftIO $ lenses `shouldBe` []
142+
143+
132144

133145
isWingmanLens :: CodeLens -> Bool
134146
isWingmanLens (CodeLens _ (Just (Command _ cmd _)) _)
Lines changed: 8 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,8 @@
1+
{-# LANGUAGE GADTs #-}
2+
3+
data Foo a where
4+
Foo :: Foo Int
5+
6+
foo :: Foo Bool -> ()
7+
foo x = case x of
8+

0 commit comments

Comments
 (0)