Skip to content

Commit 25fc54f

Browse files
committed
Use structured diagnostics for type wildcard fill suggestions
1 parent 2c200b4 commit 25fc54f

File tree

3 files changed

+116
-60
lines changed

3 files changed

+116
-60
lines changed

ghcide/src/Development/IDE/GHC/Compat/Error.hs

Lines changed: 11 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -8,6 +8,7 @@ module Development.IDE.GHC.Compat.Error (
88
-- * Error messages for the typechecking and renamer phase
99
TcRnMessage (..),
1010
TcRnMessageDetailed (..),
11+
Hole(..),
1112
stripTcRnMessageContext,
1213
-- * Parsing error message
1314
PsMessage(..),
@@ -23,9 +24,14 @@ module Development.IDE.GHC.Compat.Error (
2324
_GhcPsMessage,
2425
_GhcDsMessage,
2526
_GhcDriverMessage,
27+
_ReportHoleError,
28+
_TcRnIllegalWildcardInType,
29+
_TcRnPartialTypeSignatures,
2630
_TcRnMissingSignature,
2731
_TcRnSolverReport,
2832
_TcRnMessageWithInfo,
33+
_TypeHole,
34+
_ConstraintHole,
2935
reportContextL,
3036
reportContentL,
3137
_MismatchMessage,
@@ -38,6 +44,7 @@ import Development.IDE.GHC.Compat (Type)
3844
import GHC.Driver.Errors.Types
3945
import GHC.HsToCore.Errors.Types
4046
import GHC.Tc.Errors.Types
47+
import GHC.Tc.Types.Constraint (Hole(..), HoleSort)
4148
import GHC.Types.Error
4249

4350
-- | Some 'TcRnMessage's are nested in other constructors for additional context.
@@ -95,6 +102,10 @@ makeLensesWith
95102
(lensRules & lensField .~ mappingNamer (pure . (++ "L")))
96103
''SolverReportWithCtxt
97104

105+
makePrisms ''TcSolverReportMsg
106+
107+
makePrisms ''HoleSort
108+
98109
-- | Focus 'MismatchMsg' from 'TcSolverReportMsg'. Currently, 'MismatchMsg' can be
99110
-- extracted from 'CannotUnifyVariable' and 'Mismatch' constructors.
100111
_MismatchMessage :: Traversal' TcSolverReportMsg MismatchMsg

plugins/hls-refactor-plugin/src/Development/IDE/Plugin/Plugins/FillTypeWildcard.hs

Lines changed: 80 additions & 53 deletions
Original file line numberDiff line numberDiff line change
@@ -2,78 +2,105 @@ module Development.IDE.Plugin.Plugins.FillTypeWildcard
22
( suggestFillTypeWildcard
33
) where
44

5-
import Data.Char
6-
import qualified Data.Text as T
7-
import Language.LSP.Protocol.Types (Diagnostic (..),
8-
TextEdit (TextEdit))
5+
import Control.Lens
6+
import Data.Maybe (isJust)
7+
import qualified Data.Text as T
8+
import Development.IDE (FileDiagnostic (..),
9+
fdStructuredMessageL,
10+
printOutputable)
11+
import Development.IDE.GHC.Compat hiding (vcat)
12+
import Development.IDE.GHC.Compat.Error
13+
import Development.IDE.Types.Diagnostics (_SomeStructuredMessage)
14+
import GHC.Tc.Errors.Types (ErrInfo (..))
15+
import Language.LSP.Protocol.Types (Diagnostic (..),
16+
TextEdit (TextEdit))
917

10-
suggestFillTypeWildcard :: Diagnostic -> [(T.Text, TextEdit)]
11-
suggestFillTypeWildcard Diagnostic{_range=_range,..}
18+
suggestFillTypeWildcard :: FileDiagnostic -> [(T.Text, TextEdit)]
19+
suggestFillTypeWildcard diag@FileDiagnostic{fdLspDiagnostic = Diagnostic {..}}
1220
-- Foo.hs:3:8: error:
1321
-- * Found type wildcard `_' standing for `p -> p1 -> p'
14-
| "Found type wildcard" `T.isInfixOf` _message
15-
, " standing for " `T.isInfixOf` _message
16-
, typeSignature <- extractWildCardTypeSignature _message
17-
= [("Use type signature: ‘" <> typeSignature <> "", TextEdit _range typeSignature)]
22+
| isWildcardDiagnostic diag
23+
, typeSignature <- extractWildCardTypeSignature diag =
24+
[("Use type signature: ‘" <> typeSignature <> "", TextEdit _range typeSignature)]
1825
| otherwise = []
1926

27+
isWildcardDiagnostic :: FileDiagnostic -> Bool
28+
isWildcardDiagnostic =
29+
maybe False (isJust . (^? _TypeHole) . hole_sort) . diagReportHoleError
30+
31+
-- | Extract the 'Hole' out of a 'FileDiagnostic'
32+
diagReportHoleError :: FileDiagnostic -> Maybe Hole
33+
diagReportHoleError diag = do
34+
(solverReport, _, _) <-
35+
diag
36+
^? fdStructuredMessageL
37+
. _SomeStructuredMessage
38+
. msgEnvelopeErrorL
39+
. _TcRnMessage
40+
. _TcRnSolverReport
41+
(hole, _) <- solverReport ^? reportContentL . _ReportHoleError
42+
43+
Just hole
44+
2045
-- | Extract the type and surround it in parentheses except in obviously safe cases.
2146
--
2247
-- Inferring when parentheses are actually needed around the type signature would
2348
-- require understanding both the precedence of the context of the hole and of
2449
-- the signature itself. Inserting them (almost) unconditionally is ugly but safe.
25-
extractWildCardTypeSignature :: T.Text -> T.Text
26-
extractWildCardTypeSignature msg
27-
| enclosed || not isApp || isToplevelSig = sig
28-
| otherwise = "(" <> sig <> ")"
29-
where
30-
msgSigPart = snd $ T.breakOnEnd "standing for " msg
31-
(sig, rest) = T.span (/='') . T.dropWhile (=='') . T.dropWhile (/='') $ msgSigPart
32-
-- If we're completing something like ‘foo :: _’ parens can be safely omitted.
33-
isToplevelSig = errorMessageRefersToToplevelHole rest
34-
-- Parenthesize type applications, e.g. (Maybe Char).
35-
isApp = T.any isSpace sig
36-
-- Do not add extra parentheses to lists, tuples and already parenthesized types.
37-
enclosed =
38-
case T.uncons sig of
39-
Nothing -> error "GHC provided invalid type"
40-
Just (firstChr, _) -> not (T.null sig) && (firstChr, T.last sig) `elem` [('(', ')'), ('[', ']')]
50+
extractWildCardTypeSignature :: FileDiagnostic -> T.Text
51+
extractWildCardTypeSignature diag =
52+
case hole_ty <$> diagReportHoleError diag of
53+
Just ty
54+
| isTopLevel || not (isApp ty) || enclosed ty -> printOutputable ty
55+
| otherwise -> "(" <> printOutputable ty <> ")"
56+
Nothing -> "Uh oh!"
57+
where
58+
isTopLevel :: Bool
59+
isTopLevel =
60+
maybe False errorMessageRefersToToplevelHole (diagErrInfoContext diag)
61+
62+
isApp :: Type -> Bool
63+
isApp (AppTy _ _) = True
64+
isApp (TyConApp _ (_ : _)) = True
65+
isApp (FunTy{}) = True
66+
isApp _ = False
67+
68+
enclosed :: Type -> Bool
69+
enclosed (TyConApp con _)
70+
| con == listTyCon || isTupleTyCon con = True
71+
enclosed _ = False
72+
73+
-- | Extract the 'ErrInfo' context out of a 'FileDiagnostic' and render it to
74+
-- 'Text'
75+
diagErrInfoContext :: FileDiagnostic -> Maybe T.Text
76+
diagErrInfoContext diag = do
77+
(_, detailedMsg) <-
78+
diag
79+
^? fdStructuredMessageL
80+
. _SomeStructuredMessage
81+
. msgEnvelopeErrorL
82+
. _TcRnMessageWithCtx
83+
. _TcRnMessageWithInfo
84+
let TcRnMessageDetailed err _ = detailedMsg
85+
ErrInfo errInfoCtx _ = err
86+
87+
Just (printOutputable errInfoCtx)
4188

42-
-- | Detect whether user wrote something like @foo :: _@ or @foo :: (_, Int)@.
89+
-- | Detect whether user wrote something like @foo :: _@ or @foo :: Maybe _@.
4390
-- The former is considered toplevel case for which the function returns 'True',
4491
-- the latter is not toplevel and the returned value is 'False'.
4592
--
46-
-- When type hole is at toplevel then there’s a line starting with
47-
-- "In the type signature" which ends with " :: _" like in the
93+
-- When type hole is at toplevel then the ErrInfo context starts with
94+
-- "In the type signature" which ends with " :: _" like in the
4895
-- following snippet:
4996
--
50-
-- source/library/Language/Haskell/Brittany/Internal.hs:131:13: error:
51-
-- • Found type wildcard ‘_’ standing for ‘HsDecl GhcPs’
52-
-- To use the inferred type, enable PartialTypeSignatures
53-
-- • In the type signature: decl :: _
54-
-- In an equation for ‘splitAnnots’:
55-
-- splitAnnots m@HsModule {hsmodAnn, hsmodDecls}
56-
-- = undefined
57-
-- where
58-
-- ann :: SrcSpanAnnA
59-
-- decl :: _
60-
-- L ann decl = head hsmodDecls
61-
-- • Relevant bindings include
62-
-- [REDACTED]
97+
-- Just "In the type signature: decl :: _"
6398
--
6499
-- When type hole is not at toplevel there’s a stack of where
65100
-- the hole was located ending with "In the type signature":
66101
--
67-
-- source/library/Language/Haskell/Brittany/Internal.hs:130:20: error:
68-
-- • Found type wildcard ‘_’ standing for ‘GhcPs’
69-
-- To use the inferred type, enable PartialTypeSignatures
70-
-- • In the first argument of ‘HsDecl’, namely ‘_’
71-
-- In the type ‘HsDecl _’
72-
-- In the type signature: decl :: HsDecl _
73-
-- • Relevant bindings include
74-
-- [REDACTED]
102+
-- Just "In the first argument of ‘HsDecl’\nIn the type signature: decl :: HsDecl _"
75103
errorMessageRefersToToplevelHole :: T.Text -> Bool
76104
errorMessageRefersToToplevelHole msg =
77-
not (T.null prefix) && " :: _" `T.isSuffixOf` T.takeWhile (/= '\n') rest
78-
where
79-
(prefix, rest) = T.breakOn "• In the type signature:" msg
105+
"In the type signature:" `T.isPrefixOf` msg
106+
&& " :: _" `T.isSuffixOf` T.takeWhile (/= '\n') msg

plugins/hls-refactor-plugin/test/Main.hs

Lines changed: 25 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -701,6 +701,10 @@ typeWildCardActionTests = testGroup "type wildcard actions"
701701
"func::Integer -> Integer -> Integer"
702702
, "func x y = x + y"
703703
]
704+
, testNoUseTypeSignature "ignores typed holes"
705+
[ "func :: a -> a"
706+
, "func x = _"
707+
]
704708
, testGroup "add parens if hole is part of bigger type"
705709
[ testUseTypeSignature "subtype 1"
706710
[ "func :: _ -> Integer -> Integer"
@@ -736,19 +740,33 @@ typeWildCardActionTests = testGroup "type wildcard actions"
736740
-- | Test session of given name, checking action "Use type signature..."
737741
-- on a test file with given content and comparing to expected result.
738742
testUseTypeSignature name textIn textOut = testSession name $ do
739-
let fileStart = "module Testing where"
743+
let expectedContentAfterAction = T.unlines $ fileStart : textOut
740744
content = T.unlines $ fileStart : textIn
741-
expectedContentAfterAction = T.unlines $ fileStart : textOut
742745
doc <- createDoc "Testing.hs" "haskell" content
743-
_ <- waitForDiagnostics
744-
actionsOrCommands <- getAllCodeActions doc
745-
[addSignature] <- pure [action | InR action@CodeAction { _title = actionTitle } <- actionsOrCommands
746-
, "Use type signature" `T.isPrefixOf` actionTitle
747-
]
746+
747+
(Just addSignature) <- getUseTypeSigAction doc
748748
executeCodeAction addSignature
749749
contentAfterAction <- documentContents doc
750750
liftIO $ expectedContentAfterAction @=? contentAfterAction
751751

752+
testNoUseTypeSignature name textIn = testSession name $ do
753+
let content = T.unlines $ fileStart : textIn
754+
doc <- createDoc "Testing.hs" "haskell" content
755+
codeAction <- getUseTypeSigAction doc
756+
liftIO $ Nothing @=? codeAction
757+
758+
fileStart = "module Testing where"
759+
760+
getUseTypeSigAction docIn = do
761+
_ <- waitForDiagnostics
762+
actionsOrCommands <- getAllCodeActions docIn
763+
764+
let addSignatures =
765+
[ action | InR action@CodeAction { _title = actionTitle } <- actionsOrCommands
766+
, "Use type signature" `T.isPrefixOf` actionTitle
767+
]
768+
pure $ listToMaybe addSignatures
769+
752770

753771
removeImportTests :: TestTree
754772
removeImportTests = testGroup "remove import actions"

0 commit comments

Comments
 (0)