77
88-- | Go to the definition of a variable.
99module Development.IDE.Plugin.CodeAction
10- (
11- plugin
12-
13- -- * For haskell-language-server
14- , codeAction
15- , codeLens
16- , rulePackageExports
17- , commandHandler
10+ ( descriptor
1811
1912 -- * For testing
20- , blockCommandId
21- , typeSignatureCommandId
2213 , matchRegExMultipleImports
2314 ) where
2415
2516import Control.Monad (join , guard )
26- import Development.IDE.Plugin
2717import Development.IDE.GHC.Compat
2818import Development.IDE.Core.Rules
2919import Development.IDE.Core.RuleTypes
3020import Development.IDE.Core.Service
3121import Development.IDE.Core.Shake
3222import Development.IDE.GHC.Error
3323import Development.IDE.GHC.ExactPrint
34- import Development.IDE.LSP.Server
3524import Development.IDE.Plugin.CodeAction.ExactPrint
3625import Development.IDE.Plugin.CodeAction.PositionIndexed
3726import Development.IDE.Plugin.CodeAction.RuleTypes
3827import Development.IDE.Plugin.CodeAction.Rules
28+ import Development.IDE.Plugin.TypeLenses (suggestSignature )
3929import Development.IDE.Types.Exports
4030import Development.IDE.Types.Location
4131import Development.IDE.Types.Options
42- import Development.Shake (Rules )
4332import qualified Data.HashMap.Strict as Map
4433import qualified Language.Haskell.LSP.Core as LSP
4534import Language.Haskell.LSP.VFS
46- import Language.Haskell.LSP.Messages
4735import Language.Haskell.LSP.Types
4836import qualified Data.Rope.UTF16 as Rope
49- import Data.Aeson.Types (toJSON , fromJSON , Value (.. ), Result (.. ))
5037import Data.Char
5138import Data.Maybe
5239import Data.List.Extra
@@ -62,33 +49,28 @@ import Control.Applicative ((<|>))
6249import Safe (atMay )
6350import Bag (isEmptyBag )
6451import qualified Data.HashSet as Set
65- import Control.Concurrent.Extra (threadDelay , readVar )
52+ import Control.Concurrent.Extra (readVar )
6653import Development.IDE.GHC.Util (printRdrName )
6754import Ide.PluginUtils (subRange )
55+ import Ide.Types
6856
69- plugin :: Plugin c
70- plugin = codeActionPluginWithRules rules codeAction <> Plugin mempty setHandlersCodeLens
71-
72- rules :: Rules ()
73- rules = do
74- rulePackageExports
75-
76- -- | a command that blocks forever. Used for testing
77- blockCommandId :: T. Text
78- blockCommandId = " ghcide.command.block"
79-
80- typeSignatureCommandId :: T. Text
81- typeSignatureCommandId = " typesignature.add"
57+ descriptor :: PluginId -> PluginDescriptor IdeState
58+ descriptor plId =
59+ (defaultPluginDescriptor plId)
60+ { pluginRules = rulePackageExports,
61+ pluginCodeActionProvider = Just codeAction
62+ }
8263
8364-- | Generate code actions.
8465codeAction
8566 :: LSP. LspFuncs c
8667 -> IdeState
68+ -> PluginId
8769 -> TextDocumentIdentifier
8870 -> Range
8971 -> CodeActionContext
90- -> IO (Either ResponseError [ CAResult ] )
91- codeAction lsp state (TextDocumentIdentifier uri) _range CodeActionContext {_diagnostics= List xs} = do
72+ -> IO (Either ResponseError ( List CAResult ) )
73+ codeAction lsp state _ (TextDocumentIdentifier uri) _range CodeActionContext {_diagnostics= List xs} = do
9274 contents <- LSP. getVirtualFileFunc lsp $ toNormalizedUri uri
9375 let text = Rope. toText . (_text :: VirtualFile -> Rope. Rope ) <$> contents
9476 mbFile = toNormalizedFilePath' <$> uriToFilePath uri
@@ -122,58 +104,12 @@ codeAction lsp state (TextDocumentIdentifier uri) _range CodeActionContext{_diag
122104 <> actions
123105 <> actions'
124106 <> caRemoveInvalidExports parsedModule text diag xs uri
125- pure $ Right actions''
107+ pure $ Right $ List actions''
126108
127109mkCA :: T. Text -> [Diagnostic ] -> WorkspaceEdit -> CAResult
128110mkCA title diags edit =
129111 CACodeAction $ CodeAction title (Just CodeActionQuickFix ) (Just $ List diags) (Just edit) Nothing
130112
131- -- | Generate code lenses.
132- codeLens
133- :: LSP. LspFuncs c
134- -> IdeState
135- -> CodeLensParams
136- -> IO (Either ResponseError (List CodeLens ))
137- codeLens _lsp ideState CodeLensParams {_textDocument= TextDocumentIdentifier uri} = do
138- commandId <- makeLspCommandId " typesignature.add"
139- fmap (Right . List ) $ case uriToFilePath' uri of
140- Just (toNormalizedFilePath' -> filePath) -> do
141- _ <- runAction " codeLens" ideState (use TypeCheck filePath)
142- diag <- getDiagnostics ideState
143- hDiag <- getHiddenDiagnostics ideState
144- pure
145- [ CodeLens _range (Just (Command title commandId (Just $ List [toJSON edit]))) Nothing
146- | (dFile, _, dDiag@ Diagnostic {_range= _range}) <- diag ++ hDiag
147- , dFile == filePath
148- , (title, tedit) <- suggestSignature False dDiag
149- , let edit = WorkspaceEdit (Just $ Map. singleton uri $ List tedit) Nothing
150- ]
151- Nothing -> pure []
152-
153- -- | Execute the "typesignature.add" command.
154- commandHandler
155- :: LSP. LspFuncs c
156- -> IdeState
157- -> ExecuteCommandParams
158- -> IO (Either ResponseError Value , Maybe (ServerMethod , ApplyWorkspaceEditParams ))
159- commandHandler lsp _ideState ExecuteCommandParams {.. }
160- -- _command is prefixed with a process ID, because certain clients
161- -- have a global command registry, and all commands must be
162- -- unique. And there can be more than one ghcide instance running
163- -- at a time against the same client.
164- | T. isSuffixOf blockCommandId _command
165- = do
166- LSP. sendFunc lsp $ NotCustomServer $
167- NotificationMessage " 2.0" (CustomServerMethod " ghcide/blocking/command" ) Null
168- threadDelay maxBound
169- return (Right Null , Nothing )
170- | T. isSuffixOf typeSignatureCommandId _command
171- , Just (List [edit]) <- _arguments
172- , Success wedit <- fromJSON edit
173- = return (Right Null , Just (WorkspaceApplyEdit , ApplyWorkspaceEditParams wedit))
174- | otherwise
175- = return (Right Null , Nothing )
176-
177113suggestExactAction ::
178114 ExportsMap ->
179115 DynFlags ->
@@ -783,31 +719,6 @@ suggestFixConstructorImport _ Diagnostic{_range=_range,..}
783719 = let fixedImport = typ <> " (" <> constructor <> " )"
784720 in [(" Fix import of " <> fixedImport, [TextEdit _range fixedImport])]
785721 | otherwise = []
786-
787- suggestSignature :: Bool -> Diagnostic -> [(T. Text , [TextEdit ])]
788- suggestSignature isQuickFix Diagnostic {_range= _range@ Range {.. },.. }
789- | _message =~
790- (" (Top-level binding|Polymorphic local binding|Pattern synonym) with no type signature" :: T. Text ) = let
791- signature = removeInitialForAll
792- $ T. takeWhile (\ x -> x/= ' *' && x/= ' •' )
793- $ T. strip $ unifySpaces $ last $ T. splitOn " type signature: " $ filterNewlines _message
794- startOfLine = Position (_line _start) startCharacter
795- beforeLine = Range startOfLine startOfLine
796- title = if isQuickFix then " add signature: " <> signature else signature
797- action = TextEdit beforeLine $ signature <> " \n " <> T. replicate startCharacter " "
798- in [(title, [action])]
799- where removeInitialForAll :: T. Text -> T. Text
800- removeInitialForAll (T. breakOnEnd " :: " -> (nm, ty))
801- | " forall" `T.isPrefixOf` ty = nm <> T. drop 2 (snd (T. breakOn " ." ty))
802- | otherwise = nm <> ty
803- startCharacter
804- | " Polymorphic local binding" `T.isPrefixOf` _message
805- = _character _start
806- | otherwise
807- = 0
808-
809- suggestSignature _ _ = []
810-
811722-- | Suggests a constraint for a declaration for which a constraint is missing.
812723suggestConstraint :: DynFlags -> ParsedSource -> Diagnostic -> [(T. Text , Rewrite )]
813724suggestConstraint df parsedModule diag@ Diagnostic {.. }
@@ -1201,21 +1112,6 @@ matchRegex :: T.Text -> T.Text -> Maybe [T.Text]
12011112matchRegex message regex = case message =~~ regex of
12021113 Just (_ :: T. Text , _ :: T. Text , _ :: T. Text , bindings ) -> Just bindings
12031114 Nothing -> Nothing
1204-
1205- setHandlersCodeLens :: PartialHandlers c
1206- setHandlersCodeLens = PartialHandlers $ \ WithMessage {.. } x -> return x{
1207- LSP. codeLensHandler =
1208- withResponse RspCodeLens codeLens,
1209- LSP. executeCommandHandler =
1210- withResponseAndRequest
1211- RspExecuteCommand
1212- ReqApplyWorkspaceEdit
1213- commandHandler
1214- }
1215-
1216- filterNewlines :: T. Text -> T. Text
1217- filterNewlines = T. concat . T. lines
1218-
12191115unifySpaces :: T. Text -> T. Text
12201116unifySpaces = T. unwords . T. words
12211117
0 commit comments