Skip to content

Commit 0c9dd30

Browse files
authored
Break down ghcide functionality in HLS plugins (#1257)
* Clean up no longer needed handlers * Move some log lines to debug verbosity * Extract type signature code lenses to an HLS plugin This was worth doing to clean up the messy command handlers * Extract the block command handler to an HLS plugin Previously defined together with the type lenses command handler * fix command capability check * Extract completions into an HLS plugin We might want to break them down into multiple HLS plugins later on (local, non local, and module header). * Extract code actions into an HLS plugin * Group ghcide plugins
1 parent e06469f commit 0c9dd30

File tree

14 files changed

+214
-237
lines changed

14 files changed

+214
-237
lines changed

exe/Plugins.hs

+19-19
Original file line numberDiff line numberDiff line change
@@ -2,14 +2,14 @@
22
{-# LANGUAGE OverloadedStrings #-}
33
module Plugins where
44

5-
import Ide.Types (IdePlugins)
5+
import Ide.Types (IdePlugins)
66
import Ide.PluginUtils (pluginDescToIdePlugins)
77

88
-- fixed plugins
99
import Ide.Plugin.Example as Example
1010
import Ide.Plugin.Example2 as Example2
1111
import Development.IDE (IdeState)
12-
import Development.IDE.Plugin.HLS.GhcIde as GhcIde
12+
import Development.IDE.Plugin.HLS.GhcIde as GhcIde
1313

1414
-- haskell-language-server optional plugins
1515

@@ -89,53 +89,53 @@ idePlugins includeExamples = pluginDescToIdePlugins allPlugins
8989
then basePlugins ++ examplePlugins
9090
else basePlugins
9191
basePlugins =
92-
[ GhcIde.descriptor "ghcide"
92+
GhcIde.descriptors ++
9393
#if pragmas
94-
, Pragmas.descriptor "pragmas"
94+
Pragmas.descriptor "pragmas" :
9595
#endif
9696
#if floskell
97-
, Floskell.descriptor "floskell"
97+
Floskell.descriptor "floskell" :
9898
#endif
9999
#if fourmolu
100-
, Fourmolu.descriptor "fourmolu"
100+
Fourmolu.descriptor "fourmolu" :
101101
#endif
102102
#if tactic
103-
, Tactic.descriptor "tactic"
103+
Tactic.descriptor "tactic" :
104104
#endif
105105
#if ormolu
106-
, Ormolu.descriptor "ormolu"
106+
Ormolu.descriptor "ormolu" :
107107
#endif
108108
#if stylishHaskell
109-
, StylishHaskell.descriptor "stylish-haskell"
109+
StylishHaskell.descriptor "stylish-haskell" :
110110
#endif
111111
#if retrie
112-
, Retrie.descriptor "retrie"
112+
Retrie.descriptor "retrie" :
113113
#endif
114114
#if AGPL && brittany
115-
, Brittany.descriptor "brittany"
115+
Brittany.descriptor "brittany" :
116116
#endif
117117
#if class
118-
, Class.descriptor "class"
118+
Class.descriptor "class" :
119119
#endif
120120
#if haddockComments
121-
, HaddockComments.descriptor "haddockComments"
121+
HaddockComments.descriptor "haddockComments" :
122122
#endif
123123
#if eval
124-
, Eval.descriptor "eval"
124+
Eval.descriptor "eval" :
125125
#endif
126126
#if importLens
127-
, ExplicitImports.descriptor "importLens"
127+
ExplicitImports.descriptor "importLens" :
128128
#endif
129129
#if moduleName
130-
, ModuleName.descriptor "moduleName"
130+
ModuleName.descriptor "moduleName" :
131131
#endif
132132
#if hlint
133-
, Hlint.descriptor "hlint"
133+
Hlint.descriptor "hlint" :
134134
#endif
135135
#if splice
136-
, Splice.descriptor "splice"
136+
Splice.descriptor "splice" :
137137
#endif
138-
]
138+
[]
139139
examplePlugins =
140140
[Example.descriptor "eg"
141141
,Example2.descriptor "eg2"

ghcide/exe/Main.hs

+3-1
Original file line numberDiff line numberDiff line change
@@ -87,7 +87,9 @@ main = do
8787

8888
dir <- IO.getCurrentDirectory
8989

90-
let hlsPlugins = pluginDescToIdePlugins [GhcIde.descriptor "ghcide"]
90+
let hlsPlugins = pluginDescToIdePlugins $
91+
GhcIde.descriptors ++
92+
[ Test.blockCommandDescriptor "block-command" | argsTesting]
9193

9294
pid <- T.pack . show <$> getProcessID
9395
let hlsPlugin = asGhcIdePlugin hlsPlugins

ghcide/ghcide.cabal

+1
Original file line numberDiff line numberDiff line change
@@ -173,6 +173,7 @@ library
173173
Development.IDE.Plugin.HLS
174174
Development.IDE.Plugin.HLS.GhcIde
175175
Development.IDE.Plugin.Test
176+
Development.IDE.Plugin.TypeLenses
176177

177178
-- Unfortunately, we cannot use loadSession with ghc-lib since hie-bios uses
178179
-- the real GHC library and the types are incompatible. Furthermore, when

ghcide/src/Development/IDE/LSP/HoverDefinition.hs

+3-6
Original file line numberDiff line numberDiff line change
@@ -4,8 +4,7 @@
44

55
-- | Display information on hover.
66
module Development.IDE.LSP.HoverDefinition
7-
( setHandlersHover
8-
, setHandlersDefinition
7+
( setHandlersDefinition
98
, setHandlersTypeDefinition
109
, setHandlersDocHighlight
1110
-- * For haskell-language-server
@@ -38,13 +37,11 @@ foundHover :: (Maybe Range, [T.Text]) -> Maybe Hover
3837
foundHover (mbRange, contents) =
3938
Just $ Hover (HoverContents $ MarkupContent MkMarkdown $ T.intercalate sectionSeparator contents) mbRange
4039

41-
setHandlersDefinition, setHandlersHover, setHandlersTypeDefinition, setHandlersDocHighlight :: PartialHandlers c
40+
setHandlersDefinition, setHandlersTypeDefinition, setHandlersDocHighlight :: PartialHandlers c
4241
setHandlersDefinition = PartialHandlers $ \WithMessage{..} x ->
4342
return x{LSP.definitionHandler = withResponse RspDefinition $ const gotoDefinition}
4443
setHandlersTypeDefinition = PartialHandlers $ \WithMessage{..} x ->
45-
return x{LSP.typeDefinitionHandler = withResponse RspDefinition $ const gotoTypeDefinition}
46-
setHandlersHover = PartialHandlers $ \WithMessage{..} x ->
47-
return x{LSP.hoverHandler = withResponse RspHover $ const hover}
44+
return x {LSP.typeDefinitionHandler = withResponse RspDefinition $ const gotoTypeDefinition}
4845
setHandlersDocHighlight = PartialHandlers $ \WithMessage{..} x ->
4946
return x{LSP.documentHighlightHandler = withResponse RspDocumentHighlights $ const documentHighlight}
5047

ghcide/src/Development/IDE/LSP/LanguageServer.hs

+1-1
Original file line numberDiff line numberDiff line change
@@ -108,7 +108,7 @@ runLanguageServer options userHandlers onInitialConfig onConfigChange getIdeStat
108108
let PartialHandlers parts =
109109
initializeRequestHandler <>
110110
setHandlersIgnore <> -- least important
111-
setHandlersDefinition <> setHandlersHover <> setHandlersTypeDefinition <>
111+
setHandlersDefinition <> setHandlersTypeDefinition <>
112112
setHandlersDocHighlight <>
113113
setHandlersOutline <>
114114
userHandlers <>

ghcide/src/Development/IDE/Plugin.hs

-35
Original file line numberDiff line numberDiff line change
@@ -1,19 +1,10 @@
11
module Development.IDE.Plugin
22
( Plugin(..)
3-
, codeActionPlugin
4-
, codeActionPluginWithRules
5-
, makeLspCommandId
63
) where
74

85
import Data.Default
9-
import qualified Data.Text as T
106
import Development.Shake
117
import Development.IDE.LSP.Server
12-
import Development.IDE.Core.Rules
13-
import Ide.PluginUtils
14-
import Language.Haskell.LSP.Types
15-
import qualified Language.Haskell.LSP.Core as LSP
16-
import Language.Haskell.LSP.Messages
178

189

1910
data Plugin c = Plugin
@@ -29,29 +20,3 @@ instance Semigroup (Plugin c) where
2920

3021
instance Monoid (Plugin c) where
3122
mempty = def
32-
33-
34-
codeActionPlugin :: (LSP.LspFuncs c -> IdeState -> TextDocumentIdentifier -> Range -> CodeActionContext -> IO (Either ResponseError [CAResult])) -> Plugin c
35-
codeActionPlugin = codeActionPluginWithRules mempty
36-
37-
codeActionPluginWithRules :: Rules () -> (LSP.LspFuncs c -> IdeState -> TextDocumentIdentifier -> Range -> CodeActionContext -> IO (Either ResponseError [CAResult])) -> Plugin c
38-
codeActionPluginWithRules rr f = Plugin rr $ PartialHandlers $ \WithMessage{..} x -> return x{
39-
LSP.codeActionHandler = withResponse RspCodeAction g
40-
}
41-
where
42-
g lsp state (CodeActionParams a b c _) = fmap List <$> f lsp state a b c
43-
44-
-- | Prefix to uniquely identify commands sent to the client. This
45-
-- has two parts
46-
--
47-
-- - A representation of the process id to make sure that a client has
48-
-- unique commands if it is running multiple servers, since some
49-
-- clients have a global command table and get confused otherwise.
50-
--
51-
-- - A string to identify ghcide, to ease integration into
52-
-- haskell-language-server, which routes commands to plugins based
53-
-- on that.
54-
makeLspCommandId :: T.Text -> IO T.Text
55-
makeLspCommandId command = do
56-
pid <- getProcessID
57-
return $ T.pack (show pid) <> ":ghcide:" <> command

ghcide/src/Development/IDE/Plugin/CodeAction.hs

+14-118
Original file line numberDiff line numberDiff line change
@@ -7,46 +7,33 @@
77

88
-- | Go to the definition of a variable.
99
module 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

2516
import Control.Monad (join, guard)
26-
import Development.IDE.Plugin
2717
import Development.IDE.GHC.Compat
2818
import Development.IDE.Core.Rules
2919
import Development.IDE.Core.RuleTypes
3020
import Development.IDE.Core.Service
3121
import Development.IDE.Core.Shake
3222
import Development.IDE.GHC.Error
3323
import Development.IDE.GHC.ExactPrint
34-
import Development.IDE.LSP.Server
3524
import Development.IDE.Plugin.CodeAction.ExactPrint
3625
import Development.IDE.Plugin.CodeAction.PositionIndexed
3726
import Development.IDE.Plugin.CodeAction.RuleTypes
3827
import Development.IDE.Plugin.CodeAction.Rules
28+
import Development.IDE.Plugin.TypeLenses (suggestSignature)
3929
import Development.IDE.Types.Exports
4030
import Development.IDE.Types.Location
4131
import Development.IDE.Types.Options
42-
import Development.Shake (Rules)
4332
import qualified Data.HashMap.Strict as Map
4433
import qualified Language.Haskell.LSP.Core as LSP
4534
import Language.Haskell.LSP.VFS
46-
import Language.Haskell.LSP.Messages
4735
import Language.Haskell.LSP.Types
4836
import qualified Data.Rope.UTF16 as Rope
49-
import Data.Aeson.Types (toJSON, fromJSON, Value(..), Result(..))
5037
import Data.Char
5138
import Data.Maybe
5239
import Data.List.Extra
@@ -62,33 +49,28 @@ import Control.Applicative ((<|>))
6249
import Safe (atMay)
6350
import Bag (isEmptyBag)
6451
import qualified Data.HashSet as Set
65-
import Control.Concurrent.Extra (threadDelay, readVar)
52+
import Control.Concurrent.Extra (readVar)
6653
import Development.IDE.GHC.Util (printRdrName)
6754
import 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.
8465
codeAction
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

127109
mkCA :: T.Text -> [Diagnostic] -> WorkspaceEdit -> CAResult
128110
mkCA 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-
177113
suggestExactAction ::
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.
812723
suggestConstraint :: DynFlags -> ParsedSource -> Diagnostic -> [(T.Text, Rewrite)]
813724
suggestConstraint df parsedModule diag@Diagnostic {..}
@@ -1201,21 +1112,6 @@ matchRegex :: T.Text -> T.Text -> Maybe [T.Text]
12011112
matchRegex 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-
12191115
unifySpaces :: T.Text -> T.Text
12201116
unifySpaces = T.unwords . T.words
12211117

0 commit comments

Comments
 (0)