7
7
8
8
-- | Go to the definition of a variable.
9
9
module Development.IDE.Plugin.CodeAction
10
- (
11
- plugin
12
-
13
- -- * For haskell-language-server
14
- , codeAction
15
- , codeLens
16
- , rulePackageExports
17
- , commandHandler
10
+ ( descriptor
18
11
19
12
-- * For testing
20
- , blockCommandId
21
- , typeSignatureCommandId
22
13
, matchRegExMultipleImports
23
14
) where
24
15
25
16
import Control.Monad (join , guard )
26
- import Development.IDE.Plugin
27
17
import Development.IDE.GHC.Compat
28
18
import Development.IDE.Core.Rules
29
19
import Development.IDE.Core.RuleTypes
30
20
import Development.IDE.Core.Service
31
21
import Development.IDE.Core.Shake
32
22
import Development.IDE.GHC.Error
33
23
import Development.IDE.GHC.ExactPrint
34
- import Development.IDE.LSP.Server
35
24
import Development.IDE.Plugin.CodeAction.ExactPrint
36
25
import Development.IDE.Plugin.CodeAction.PositionIndexed
37
26
import Development.IDE.Plugin.CodeAction.RuleTypes
38
27
import Development.IDE.Plugin.CodeAction.Rules
28
+ import Development.IDE.Plugin.TypeLenses (suggestSignature )
39
29
import Development.IDE.Types.Exports
40
30
import Development.IDE.Types.Location
41
31
import Development.IDE.Types.Options
42
- import Development.Shake (Rules )
43
32
import qualified Data.HashMap.Strict as Map
44
33
import qualified Language.Haskell.LSP.Core as LSP
45
34
import Language.Haskell.LSP.VFS
46
- import Language.Haskell.LSP.Messages
47
35
import Language.Haskell.LSP.Types
48
36
import qualified Data.Rope.UTF16 as Rope
49
- import Data.Aeson.Types (toJSON , fromJSON , Value (.. ), Result (.. ))
50
37
import Data.Char
51
38
import Data.Maybe
52
39
import Data.List.Extra
@@ -62,33 +49,28 @@ import Control.Applicative ((<|>))
62
49
import Safe (atMay )
63
50
import Bag (isEmptyBag )
64
51
import qualified Data.HashSet as Set
65
- import Control.Concurrent.Extra (threadDelay , readVar )
52
+ import Control.Concurrent.Extra (readVar )
66
53
import Development.IDE.GHC.Util (printRdrName )
67
54
import Ide.PluginUtils (subRange )
55
+ import Ide.Types
68
56
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
+ }
82
63
83
64
-- | Generate code actions.
84
65
codeAction
85
66
:: LSP. LspFuncs c
86
67
-> IdeState
68
+ -> PluginId
87
69
-> TextDocumentIdentifier
88
70
-> Range
89
71
-> 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
92
74
contents <- LSP. getVirtualFileFunc lsp $ toNormalizedUri uri
93
75
let text = Rope. toText . (_text :: VirtualFile -> Rope. Rope ) <$> contents
94
76
mbFile = toNormalizedFilePath' <$> uriToFilePath uri
@@ -122,58 +104,12 @@ codeAction lsp state (TextDocumentIdentifier uri) _range CodeActionContext{_diag
122
104
<> actions
123
105
<> actions'
124
106
<> caRemoveInvalidExports parsedModule text diag xs uri
125
- pure $ Right actions''
107
+ pure $ Right $ List actions''
126
108
127
109
mkCA :: T. Text -> [Diagnostic ] -> WorkspaceEdit -> CAResult
128
110
mkCA title diags edit =
129
111
CACodeAction $ CodeAction title (Just CodeActionQuickFix ) (Just $ List diags) (Just edit) Nothing
130
112
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
-
177
113
suggestExactAction ::
178
114
ExportsMap ->
179
115
DynFlags ->
@@ -783,31 +719,6 @@ suggestFixConstructorImport _ Diagnostic{_range=_range,..}
783
719
= let fixedImport = typ <> " (" <> constructor <> " )"
784
720
in [(" Fix import of " <> fixedImport, [TextEdit _range fixedImport])]
785
721
| 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
-
811
722
-- | Suggests a constraint for a declaration for which a constraint is missing.
812
723
suggestConstraint :: DynFlags -> ParsedSource -> Diagnostic -> [(T. Text , Rewrite )]
813
724
suggestConstraint df parsedModule diag@ Diagnostic {.. }
@@ -1201,21 +1112,6 @@ matchRegex :: T.Text -> T.Text -> Maybe [T.Text]
1201
1112
matchRegex message regex = case message =~~ regex of
1202
1113
Just (_ :: T. Text , _ :: T. Text , _ :: T. Text , bindings ) -> Just bindings
1203
1114
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
-
1219
1115
unifySpaces :: T. Text -> T. Text
1220
1116
unifySpaces = T. unwords . T. words
1221
1117
0 commit comments