@@ -15,37 +15,38 @@ module Development.IDE.Plugin.TypeLenses (
1515
1616import Control.Concurrent.STM.Stats (atomically )
1717import Control.DeepSeq (rwhnf )
18+ import Control.Lens ((?~) )
1819import Control.Monad (mzero )
1920import Control.Monad.Extra (whenMaybe )
2021import Control.Monad.IO.Class (MonadIO (liftIO ))
2122import Control.Monad.Trans.Class (MonadTrans (lift ))
22- import Data.Aeson.Types (Value , toJSON )
23+ import Data.Aeson.Types (toJSON )
2324import qualified Data.Aeson.Types as A
2425import Data.List (find )
2526import qualified Data.Map as Map
26- import Data.Maybe (catMaybes , mapMaybe )
27+ import Data.Maybe (catMaybes , fromMaybe ,
28+ maybeToList )
2729import qualified Data.Text as T
2830import Development.IDE (GhcSession (.. ),
2931 HscEnvEq (hscEnv ),
30- RuleResult , Rules ,
32+ RuleResult , Rules , Uri ,
3133 define , srcSpanToRange ,
3234 usePropertyAction )
3335import Development.IDE.Core.Compile (TcModuleResult (.. ))
3436import Development.IDE.Core.PluginUtils
3537import Development.IDE.Core.PositionMapping (PositionMapping ,
38+ fromCurrentRange ,
3639 toCurrentRange )
3740import Development.IDE.Core.Rules (IdeState , runAction )
38- import Development.IDE.Core.RuleTypes (GetBindings (GetBindings ),
39- TypeCheck (TypeCheck ))
41+ import Development.IDE.Core.RuleTypes (TypeCheck (TypeCheck ))
4042import Development.IDE.Core.Service (getDiagnostics )
4143import Development.IDE.Core.Shake (getHiddenDiagnostics ,
4244 use )
4345import qualified Development.IDE.Core.Shake as Shake
4446import Development.IDE.GHC.Compat
4547import Development.IDE.GHC.Util (printName )
4648import Development.IDE.Graph.Classes
47- import Development.IDE.Spans.LocalBindings (Bindings , getFuzzyScope )
48- import Development.IDE.Types.Location (Position (Position , _character , _line ),
49+ import Development.IDE.Types.Location (Position (Position , _line ),
4950 Range (Range , _end , _start ))
5051import GHC.Generics (Generic )
5152import Ide.Logger (Pretty (pretty ),
@@ -60,38 +61,43 @@ import Ide.Types (CommandFunction,
6061 PluginDescriptor (.. ),
6162 PluginId ,
6263 PluginMethodHandler ,
64+ ResolveFunction ,
6365 configCustomConfig ,
6466 defaultConfigDescriptor ,
6567 defaultPluginDescriptor ,
6668 mkCustomConfig ,
67- mkPluginHandler )
68- import Language.LSP.Protocol.Message (Method (Method_TextDocumentCodeLens ),
69+ mkPluginHandler ,
70+ mkResolveHandler )
71+ import qualified Language.LSP.Protocol.Lens as L
72+ import Language.LSP.Protocol.Message (Method (Method_CodeLensResolve , Method_TextDocumentCodeLens ),
6973 SMethod (.. ))
7074import Language.LSP.Protocol.Types (ApplyWorkspaceEditParams (ApplyWorkspaceEditParams ),
71- CodeLens (CodeLens ),
75+ CodeLens (.. ),
7276 CodeLensParams (CodeLensParams , _textDocument ),
73- Diagnostic (.. ),
77+ Command , Diagnostic (.. ),
7478 Null (Null ),
7579 TextDocumentIdentifier (TextDocumentIdentifier ),
7680 TextEdit (TextEdit ),
7781 WorkspaceEdit (WorkspaceEdit ),
7882 type (|? ) (.. ))
7983import qualified Language.LSP.Server as LSP
80- import Text.Regex.TDFA ((=~) , (=~~) )
84+ import Text.Regex.TDFA ((=~) )
8185
8286data Log = LogShake Shake. Log deriving Show
8387
8488instance Pretty Log where
8589 pretty = \ case
8690 LogShake log -> pretty log
8791
92+
8893typeLensCommandId :: T. Text
8994typeLensCommandId = " typesignature.add"
9095
9196descriptor :: Recorder (WithPriority Log ) -> PluginId -> PluginDescriptor IdeState
9297descriptor recorder plId =
9398 (defaultPluginDescriptor plId)
9499 { pluginHandlers = mkPluginHandler SMethod_TextDocumentCodeLens codeLensProvider
100+ <> mkResolveHandler SMethod_CodeLensResolve codeLensResolveProvider
95101 , pluginCommands = [PluginCommand (CommandId typeLensCommandId) " adds a signature" commandHandler]
96102 , pluginRules = rules recorder
97103 , pluginConfigDescriptor = defaultConfigDescriptor {configCustomConfig = mkCustomConfig properties}
@@ -109,97 +115,115 @@ codeLensProvider :: PluginMethodHandler IdeState Method_TextDocumentCodeLens
109115codeLensProvider ideState pId CodeLensParams {_textDocument = TextDocumentIdentifier uri} = do
110116 mode <- liftIO $ runAction " codeLens.config" ideState $ usePropertyAction # mode pId properties
111117 nfp <- getNormalizedFilePathE uri
112- env <- hscEnv . fst <$>
113- runActionE " codeLens.GhcSession" ideState
114- (useWithStaleE GhcSession nfp)
115-
116- (tmr, _) <- runActionE " codeLens.TypeCheck" ideState
117- (useWithStaleE TypeCheck nfp)
118-
119- (bindings, _) <- runActionE " codeLens.GetBindings" ideState
120- (useWithStaleE GetBindings nfp)
121-
122- (gblSigs@ (GlobalBindingTypeSigsResult gblSigs'), gblSigsMp) <-
123- runActionE " codeLens.GetGlobalBindingTypeSigs" ideState
124- (useWithStaleE GetGlobalBindingTypeSigs nfp)
125-
126- diag <- liftIO $ atomically $ getDiagnostics ideState
127- hDiag <- liftIO $ atomically $ getHiddenDiagnostics ideState
128-
129- let toWorkSpaceEdit tedit = WorkspaceEdit (Just $ Map. singleton uri $ tedit) Nothing Nothing
130- generateLensForGlobal mp sig@ GlobalBindingTypeSig {gbRendered} = do
131- range <- toCurrentRange mp =<< srcSpanToRange (gbSrcSpan sig)
132- tedit <- gblBindingTypeSigToEdit sig (Just gblSigsMp)
133- let wedit = toWorkSpaceEdit [tedit]
134- pure $ generateLens pId range (T. pack gbRendered) wedit
135- generateLensFromDiags f =
136- [ generateLens pId _range title edit
137- | (dFile, _, dDiag@ Diagnostic {_range = _range}) <- diag ++ hDiag
138- , dFile == nfp
139- , (title, tedit) <- f dDiag
140- , let edit = toWorkSpaceEdit tedit
141- ]
142- -- `suggestLocalSignature` relies on diagnostic, if diagnostics don't have the local signature warning,
143- -- the `bindings` is useless, and if diagnostic has, that means we parsed success, and the `bindings` is fresh.
144- pure $ InL $ case mode of
145- Always ->
146- mapMaybe (generateLensForGlobal gblSigsMp) gblSigs'
147- <> generateLensFromDiags
148- (suggestLocalSignature False (Just env) (Just tmr) (Just bindings)) -- we still need diagnostics for local bindings
149- Exported -> mapMaybe (generateLensForGlobal gblSigsMp) (filter gbExported gblSigs')
150- Diagnostics -> generateLensFromDiags
151- $ suggestSignature False (Just env) (Just gblSigs) (Just tmr) (Just bindings)
152-
153- generateLens :: PluginId -> Range -> T. Text -> WorkspaceEdit -> CodeLens
154- generateLens pId _range title edit =
155- let cId = mkLspCommand pId (CommandId typeLensCommandId) title (Just [toJSON edit])
156- in CodeLens _range (Just cId) Nothing
157-
118+ -- We have two ways we can possibly generate code lenses for type lenses.
119+ -- Different options are with different "modes" of the type-lenses plugin.
120+ -- (Remember here, as the code lens is not resolved yet, we only really need
121+ -- the range and any data that will help us resolve it later)
122+ let -- The first option is to generate lens from diagnostics about
123+ -- top level bindings.
124+ generateLensFromGlobalDiags diags =
125+ -- We don't actually pass any data to resolve, however we need this
126+ -- dummy type to make sure HLS resolves our lens
127+ [ CodeLens _range Nothing (Just $ toJSON TypeLensesResolve )
128+ | (dFile, _, diag@ Diagnostic {_range}) <- diags
129+ , dFile == nfp
130+ , isGlobalDiagnostic diag]
131+ -- The second option is to generate lenses from the GlobalBindingTypeSig
132+ -- rule. This is the only type that needs to have the range adjusted
133+ -- with PositionMapping.
134+ -- PositionMapping for diagnostics doesn't make sense, because we always
135+ -- have fresh diagnostics even if current module parsed failed (the
136+ -- diagnostic would then be parse failed). See
137+ -- https://github.com/haskell/haskell-language-server/pull/3558 for this
138+ -- discussion.
139+ generateLensFromGlobal sigs mp = do
140+ [ CodeLens newRange Nothing (Just $ toJSON TypeLensesResolve )
141+ | sig <- sigs
142+ , Just range <- [srcSpanToRange (gbSrcSpan sig)]
143+ , Just newRange <- [toCurrentRange mp range]]
144+ if mode == Always || mode == Exported
145+ then do
146+ -- In this mode we get the global bindings from the
147+ -- GlobalBindingTypeSigs rule.
148+ (GlobalBindingTypeSigsResult gblSigs, gblSigsMp) <-
149+ runActionE " codeLens.GetGlobalBindingTypeSigs" ideState
150+ $ useWithStaleE GetGlobalBindingTypeSigs nfp
151+ -- Depending on whether we only want exported or not we filter our list
152+ -- of signatures to get what we want
153+ let relevantGlobalSigs =
154+ if mode == Exported
155+ then filter gbExported gblSigs
156+ else gblSigs
157+ pure $ InL $ generateLensFromGlobal relevantGlobalSigs gblSigsMp
158+ else do
159+ -- For this mode we exclusively use diagnostics to create the lenses.
160+ -- However we will still use the GlobalBindingTypeSigs to resolve them.
161+ diags <- liftIO $ atomically $ getDiagnostics ideState
162+ hDiags <- liftIO $ atomically $ getHiddenDiagnostics ideState
163+ let allDiags = diags <> hDiags
164+ pure $ InL $ generateLensFromGlobalDiags allDiags
165+
166+ codeLensResolveProvider :: ResolveFunction IdeState TypeLensesResolve Method_CodeLensResolve
167+ codeLensResolveProvider ideState pId lens@ CodeLens {_range} uri TypeLensesResolve = do
168+ nfp <- getNormalizedFilePathE uri
169+ (gblSigs@ (GlobalBindingTypeSigsResult _), pm) <-
170+ runActionE " codeLens.GetGlobalBindingTypeSigs" ideState
171+ $ useWithStaleE GetGlobalBindingTypeSigs nfp
172+ -- regardless of how the original lens was generated, we want to get the range
173+ -- that the global bindings rule would expect here, hence the need to reverse
174+ -- position map the range, regardless of whether it was position mapped in the
175+ -- beginning or freshly taken from diagnostics.
176+ newRange <- handleMaybe PluginStaleResolve (fromCurrentRange pm _range)
177+ -- We also pass on the PositionMapping so that the generated text edit can
178+ -- have the range adjusted.
179+ (title, edit) <-
180+ handleMaybe PluginStaleResolve $ suggestGlobalSignature' False (Just gblSigs) (Just pm) newRange
181+ pure $ lens & L. command ?~ generateLensCommand pId uri title edit
182+
183+ generateLensCommand :: PluginId -> Uri -> T. Text -> TextEdit -> Command
184+ generateLensCommand pId uri title edit =
185+ let wEdit = WorkspaceEdit (Just $ Map. singleton uri $ [edit]) Nothing Nothing
186+ in mkLspCommand pId (CommandId typeLensCommandId) title (Just [toJSON wEdit])
187+
188+ -- Since the lenses are created with diagnostics, and since the globalTypeSig
189+ -- rule can't be changed as it is also used by the hls-refactor plugin, we can't
190+ -- rely on actions. Because we can't rely on actions it doesn't make sense to
191+ -- recompute the edit upon command. Hence the command here just takes a edit
192+ -- and applies it.
158193commandHandler :: CommandFunction IdeState WorkspaceEdit
159194commandHandler _ideState wedit = do
160195 _ <- lift $ LSP. sendRequest SMethod_WorkspaceApplyEdit (ApplyWorkspaceEditParams Nothing wedit) (\ _ -> pure () )
161196 pure $ InR Null
162197
163198--------------------------------------------------------------------------------
199+ suggestSignature :: Bool -> Maybe GlobalBindingTypeSigsResult -> Diagnostic -> [(T. Text , TextEdit )]
200+ suggestSignature isQuickFix mGblSigs diag =
201+ maybeToList (suggestGlobalSignature isQuickFix mGblSigs diag)
202+
203+ -- The suggestGlobalSignature is separated into two functions. The main function
204+ -- works with a diagnostic, which then calls the secondary function with
205+ -- whatever pieces of the diagnostic it needs. This allows the resolve function,
206+ -- which no longer has the Diagnostic, to still call the secondary functions.
207+ suggestGlobalSignature :: Bool -> Maybe GlobalBindingTypeSigsResult -> Diagnostic -> Maybe (T. Text , TextEdit )
208+ suggestGlobalSignature isQuickFix mGblSigs diag@ Diagnostic {_range}
209+ | isGlobalDiagnostic diag =
210+ suggestGlobalSignature' isQuickFix mGblSigs Nothing _range
211+ | otherwise = Nothing
164212
165- suggestSignature :: Bool -> Maybe HscEnv -> Maybe GlobalBindingTypeSigsResult -> Maybe TcModuleResult -> Maybe Bindings -> Diagnostic -> [(T. Text , [TextEdit ])]
166- suggestSignature isQuickFix env mGblSigs mTmr mBindings diag =
167- suggestGlobalSignature isQuickFix mGblSigs diag <> suggestLocalSignature isQuickFix env mTmr mBindings diag
213+ isGlobalDiagnostic :: Diagnostic -> Bool
214+ isGlobalDiagnostic Diagnostic {_message} = _message =~ (" (Top-level binding|Pattern synonym) with no type signature" :: T. Text )
168215
169- suggestGlobalSignature :: Bool -> Maybe GlobalBindingTypeSigsResult -> Diagnostic -> [( T. Text , [ TextEdit ])]
170- suggestGlobalSignature isQuickFix mGblSigs Diagnostic {_message, _range}
171- | _message
172- =~ ( " (Top-level binding|Pattern synonym) with no type signature " :: T. Text )
173- , Just (GlobalBindingTypeSigsResult sigs) <- mGblSigs
174- , Just sig <- find (\ x -> sameThing (gbSrcSpan x) _range ) sigs
216+ -- If a PositionMapping is supplied, this function will call
217+ -- gblBindingTypeSigToEdit with it to create a TextEdit in the right location.
218+ suggestGlobalSignature' :: Bool -> Maybe GlobalBindingTypeSigsResult -> Maybe PositionMapping -> Range -> Maybe ( T. Text , TextEdit )
219+ suggestGlobalSignature' isQuickFix mGblSigs pm range
220+ | Just (GlobalBindingTypeSigsResult sigs) <- mGblSigs
221+ , Just sig <- find (\ x -> sameThing (gbSrcSpan x) range ) sigs
175222 , signature <- T. pack $ gbRendered sig
176223 , title <- if isQuickFix then " add signature: " <> signature else signature
177- , Just action <- gblBindingTypeSigToEdit sig Nothing =
178- [(title, [action])]
179- | otherwise = []
180-
181- suggestLocalSignature :: Bool -> Maybe HscEnv -> Maybe TcModuleResult -> Maybe Bindings -> Diagnostic -> [(T. Text , [TextEdit ])]
182- suggestLocalSignature isQuickFix mEnv mTmr mBindings Diagnostic {_message, _range = _range@ Range {.. }}
183- | Just (_ :: T. Text , _ :: T. Text , _ :: T. Text , [identifier ]) <-
184- (T. unwords . T. words $ _message)
185- =~~ (" Polymorphic local binding with no type signature: (.*) ::" :: T. Text )
186- , Just bindings <- mBindings
187- , Just env <- mEnv
188- , localScope <- getFuzzyScope bindings _start _end
189- , -- we can't use srcspan to lookup scoped bindings, because the error message reported by GHC includes the entire binding, instead of simply the name
190- Just (name, ty) <- find (\ (x, _) -> printName x == T. unpack identifier) localScope >>= \ (name, mTy) -> (name,) <$> mTy
191- , Just TcModuleResult {tmrTypechecked = TcGblEnv {tcg_rdr_env, tcg_sigs}} <- mTmr
192- , -- not a top-level thing, to avoid duplication
193- not $ name `elemNameSet` tcg_sigs
194- , tyMsg <- printSDocQualifiedUnsafe (mkPrintUnqualifiedDefault env tcg_rdr_env) $ pprSigmaType ty
195- , signature <- T. pack $ printName name <> " :: " <> tyMsg
196- , startCharacter <- _character _start
197- , startOfLine <- Position (_line _start) startCharacter
198- , beforeLine <- Range startOfLine startOfLine
199- , title <- if isQuickFix then " add signature: " <> signature else signature
200- , action <- TextEdit beforeLine $ signature <> " \n " <> T. replicate (fromIntegral startCharacter) " " =
201- [(title, [action])]
202- | otherwise = []
224+ , Just action <- gblBindingTypeSigToEdit sig pm =
225+ Just (title, action)
226+ | otherwise = Nothing
203227
204228sameThing :: SrcSpan -> Range -> Bool
205229sameThing s1 s2 = (_start <$> srcSpanToRange s1) == (_start <$> Just s2)
@@ -209,12 +233,20 @@ gblBindingTypeSigToEdit GlobalBindingTypeSig{..} mmp
209233 | Just Range {.. } <- srcSpanToRange $ getSrcSpan gbName
210234 , startOfLine <- Position (_line _start) 0
211235 , beforeLine <- Range startOfLine startOfLine
212- -- If `mmp` is `Nothing`, return the original range, it used by lenses from diagnostic,
236+ -- If `mmp` is `Nothing`, return the original range,
213237 -- otherwise we apply `toCurrentRange`, and the guard should fail if `toCurrentRange` failed.
214238 , Just range <- maybe (Just beforeLine) (flip toCurrentRange beforeLine) mmp
215- = Just $ TextEdit range $ T. pack gbRendered <> " \n "
239+ -- We need to flatten the signature, as otherwise long signatures are
240+ -- rendered on multiple lines with invalid formatting.
241+ , renderedFlat <- unwords $ lines gbRendered
242+ = Just $ TextEdit range $ T. pack renderedFlat <> " \n "
216243 | otherwise = Nothing
217244
245+ -- | We don't need anything to resolve our lens, but a data field is mandatory
246+ -- to get types resolved in HLS
247+ data TypeLensesResolve = TypeLensesResolve
248+ deriving (Generic , A.FromJSON , A.ToJSON )
249+
218250data Mode
219251 = -- | always displays type lenses of global bindings, no matter what GHC flags are set
220252 Always
0 commit comments