@@ -2,78 +2,106 @@ 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+ . _1
42+ (hole, _) <- solverReport ^? reportContentL . _ReportHoleError
43+
44+ Just hole
45+
2046-- | Extract the type and surround it in parentheses except in obviously safe cases.
2147--
2248-- Inferring when parentheses are actually needed around the type signature would
2349-- require understanding both the precedence of the context of the hole and of
2450-- 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
51+ extractWildCardTypeSignature :: FileDiagnostic -> T. Text
52+ extractWildCardTypeSignature diag =
53+ case hole_ty <$> diagReportHoleError diag of
54+ Just ty
55+ | isTopLevel || not (isApp ty) || enclosed ty -> printOutputable ty
56+ | otherwise -> " (" <> printOutputable ty <> " )"
3957 Nothing -> error " GHC provided invalid type"
40- Just (firstChr, _) -> not (T. null sig) && (firstChr, T. last sig) `elem` [(' (' , ' )' ), (' [' , ' ]' )]
58+ where
59+ isTopLevel :: Bool
60+ isTopLevel =
61+ maybe False errorMessageRefersToToplevelHole (diagErrInfoContext diag)
62+
63+ isApp :: Type -> Bool
64+ isApp (AppTy _ _) = True
65+ isApp (TyConApp _ (_ : _)) = True
66+ isApp (FunTy {}) = True
67+ isApp _ = False
68+
69+ enclosed :: Type -> Bool
70+ enclosed (TyConApp con _)
71+ | con == listTyCon || isTupleTyCon con = True
72+ enclosed _ = False
73+
74+ -- | Extract the 'ErrInfo' context out of a 'FileDiagnostic' and render it to
75+ -- 'Text'
76+ diagErrInfoContext :: FileDiagnostic -> Maybe T. Text
77+ diagErrInfoContext diag = do
78+ (_, detailedMsg) <-
79+ diag
80+ ^? fdStructuredMessageL
81+ . _SomeStructuredMessage
82+ . msgEnvelopeErrorL
83+ . _TcRnMessageWithCtx
84+ . _TcRnMessageWithInfo
85+ let TcRnMessageDetailed err _ = detailedMsg
86+ ErrInfo errInfoCtx _ = err
87+
88+ Just (printOutputable errInfoCtx)
4189
42- -- | Detect whether user wrote something like @foo :: _@ or @foo :: (_, Int) @.
90+ -- | Detect whether user wrote something like @foo :: _@ or @foo :: Maybe _ @.
4391-- The former is considered toplevel case for which the function returns 'True',
4492-- the latter is not toplevel and the returned value is 'False'.
4593--
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
94+ -- When type hole is at toplevel then the ErrInfo context starts with
95+ -- "In the type signature" which ends with " :: _" like in the
4896-- following snippet:
4997--
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]
98+ -- Just "In the type signature: decl :: _"
6399--
64100-- When type hole is not at toplevel there’s a stack of where
65101-- the hole was located ending with "In the type signature":
66102--
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]
103+ -- Just "In the first argument of ‘HsDecl’\nIn the type signature: decl :: HsDecl _"
75104errorMessageRefersToToplevelHole :: T. Text -> Bool
76105errorMessageRefersToToplevelHole msg =
77- not (T. null prefix) && " :: _" `T.isSuffixOf` T. takeWhile (/= ' \n ' ) rest
78- where
79- (prefix, rest) = T. breakOn " • In the type signature:" msg
106+ " In the type signature:" `T.isPrefixOf` msg
107+ && " :: _" `T.isSuffixOf` T. takeWhile (/= ' \n ' ) msg
0 commit comments