Skip to content

Commit df02ff2

Browse files
pepeiborralukel97
authored andcommitted
1 parent baabffd commit df02ff2

File tree

3 files changed

+395
-0
lines changed

3 files changed

+395
-0
lines changed

docs/imports.gif

140 KB
Loading

docs/plugin-tutorial.md

Lines changed: 395 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,395 @@
1+
# Let’s write a Haskell Language Server plugin
2+
3+
Haskell Language Server is an LSP server for the Haskell programming language. It builds on several previous efforts
4+
to create a Haskell IDE, you can find many more details on the history and architecture in the [IDE 2020](https://mpickering.github.io/ide/index.html) community page.
5+
6+
In this article we are going to cover the creation of an HLS plugin from scratch: a code lens to display explicit import lists.
7+
Along the way we will learn about HLS, its plugin model, and the relationship with ghcide and LSP.
8+
9+
## Introduction
10+
11+
Writing plugins for HLS is a joy. Personally, I enjoy the ability to tap into the gigantic bag of goodies that is GHC, as well as the IDE integration thanks to LSP.
12+
13+
In the last couple of months I have written various HLS (and ghcide) plugins for things like:
14+
15+
1. Suggest imports for variables not in scope,
16+
2. Remove redundant imports,
17+
2. Evaluate code in comments (a la doctest),
18+
3. Integrate the retrie refactoring library.
19+
20+
These plugins are small but meaningful steps towards a more polished IDE experience, and in writing them I didn't have to worry about performance, UI, distribution, or even think for the most part, since it's always another tool (usually GHC) doing all the heavy lifting. The plugins also make these tools much more accessible to all the users of HLS.
21+
22+
## The task
23+
24+
Here is a visual statement of what we want to accomplish:
25+
26+
![Imports code lens](imports.gif)
27+
28+
And here is the gist of the algorithm:
29+
30+
1. Request the type checking artefacts from the ghcide subsystem
31+
2. Extract the actual import lists from the type checked AST,
32+
3. Ask GHC to produce the minimal import lists for this AST,
33+
4. For every import statement without a explicit import list, find out the minimal import list, and produce a code lens to display it together with a command to graft it on.
34+
35+
## Setup
36+
37+
To get started, let’s fetch the HLS repo and build it. You need at least GHC 8.6 for this:
38+
39+
```
40+
git clone --recursive http://github.com/haskell/haskell-language-server hls
41+
cd hls
42+
cabal update
43+
cabal build
44+
```
45+
46+
If you run into any issues trying to build the binaries, the #haskell-ide-engine IRC chat room in
47+
Freenode is always a good place to ask for help.
48+
49+
Once cabal is done take a note of the location of the `haskell-language-server` binary and point your LSP client to it. In VSCode this is done by editing the "Haskell Server Executable Path" setting. This way you can simply test your changes by reloading your editor after rebuilding the binary.
50+
51+
![Settings](settings-vscode.png)
52+
53+
## Anatomy of a plugin
54+
55+
HLS plugins are values of the `Plugin` datatype, which is defined in `Ide.Plugin` as:
56+
```haskell
57+
data PluginDescriptor =
58+
PluginDescriptor { pluginId :: !PluginId
59+
, pluginRules :: !(Rules ())
60+
, pluginCommands :: ![PluginCommand]
61+
, pluginCodeActionProvider :: !(Maybe CodeActionProvider)
62+
, pluginCodeLensProvider :: !(Maybe CodeLensProvider)
63+
, pluginHoverProvider :: !(Maybe HoverProvider)
64+
, pluginSymbolsProvider :: !(Maybe SymbolsProvider)
65+
, pluginFormattingProvider :: !(Maybe (FormattingProvider IO))
66+
, pluginCompletionProvider :: !(Maybe CompletionProvider)
67+
, pluginRenameProvider :: !(Maybe RenameProvider)
68+
}
69+
```
70+
A plugin has a unique id, a set of rules, a set of command handlers, and a set of "providers":
71+
72+
* Rules add new targets to the Shake build graph defined in ghcide. 99% of plugins need not define any new rules.
73+
* Commands are an LSP abstraction for actions initiated by the user which are handled in the server. These actions can be long running and involve multiple modules. Many plugins define command handlers.
74+
* Providers are a query-like abstraction where the LSP client asks the server for information. These queries must be fulfilled as quickly as possible.
75+
76+
The HLS codebase includes several plugins under the namespace `Ide.Plugin.*`, the most relevant are:
77+
78+
- The ghcide plugin, which embeds ghcide as a plugin (ghcide is also the engine under HLS).
79+
- The example and example2 plugins, offering a dubious welcome to new contributors
80+
- The Brittany, ormolu, fourmolu, floskell and stylish-haskell plugins, a testament to the code formatting wars of our community.
81+
- The eval plugin, a code lens provider to evaluate code in comments
82+
- The retrie plugin, a code actions provider to execute retrie commands
83+
84+
I would recommend looking at the existing plugins for inspiration and reference.
85+
86+
Plugins are "linked" in the `Main` module, so we will need to add our plugin there once we have defined it:
87+
88+
```haskell
89+
idePlugins = pluginDescToIdePlugins allPlugins
90+
where
91+
allPlugins =
92+
[ GhcIde.descriptor "ghcide"
93+
, Pragmas.descriptor "pragmas"
94+
, Floskell.descriptor "floskell"
95+
, Fourmolu.descriptor "fourmolu"
96+
, Ormolu.descriptor "ormolu"
97+
, StylishHaskell.descriptor "stylish-haskell"
98+
, Retrie.descriptor "retrie"
99+
#if AGPL
100+
, Brittany.descriptor "brittany"
101+
#endif
102+
, Eval.descriptor "eval"
103+
]
104+
```
105+
To add a new plugin, simply extend the list of `allPlugins` and rebuild.
106+
107+
## Providers
108+
109+
99% of plugins will want to define at least one type of provider. But what is a provider? Let's take a look at some types:
110+
```haskell
111+
type CodeActionProvider = LSP.LspFuncs Config
112+
-> IdeState
113+
-> PluginId
114+
-> TextDocumentIdentifier
115+
-> Range
116+
-> CodeActionContext
117+
-> IO (Either ResponseError (List CAResult))
118+
119+
type CompletionProvider = LSP.LspFuncs Config
120+
-> IdeState
121+
-> CompletionParams
122+
-> IO (Either ResponseError CompletionResponseResult)
123+
124+
type CodeLensProvider = LSP.LspFuncs Config
125+
-> IdeState
126+
-> PluginId
127+
-> CodeLensParams
128+
-> IO (Either ResponseError (List CodeLens))
129+
130+
type RenameProvider = LSP.LspFuncs Config
131+
-> IdeState
132+
-> RenameParams
133+
-> IO (Either ResponseError WorkspaceEdit)
134+
```
135+
136+
Providers are functions that receive some inputs and produce an IO computation that returns either an error or some result.
137+
138+
All providers receive an `LSP.LspFuncs` value, which is a record of functions to perform LSP actions. Most providers can safely ignore this argument, since the LSP interaction is automatically managed by HLS.
139+
Some of its capabilities are:
140+
- Querying the LSP client capabilities
141+
- Manual progress reporting and cancellation, for plugins that provide long running commands (like the Retrie plugin),
142+
- Custom user interactions via [message dialogs](https://microsoft.github.io/language-server-protocol/specification#window_showMessage). For instance, the Retrie plugin uses this to report skipped modules.
143+
144+
The second argument plugins receive is `IdeState`, which encapsulates all the ghcide state including the build graph. This allows to request ghcide rule results, which leverages Shake to parallelize and reuse previous results as appropriate. Rule types are instances of the `RuleResult` type family, and
145+
most of them are defined in `Development.IDE.Core.RuleTypes`. Some relevant rule types are:
146+
```haskell
147+
-- | The parse tree for the file using GetFileContents
148+
type instance RuleResult GetParsedModule = ParsedModule
149+
150+
-- | The type checked version of this file
151+
type instance RuleResult TypeCheck = TcModuleResult
152+
153+
-- | A GHC session that we reuse.
154+
type instance RuleResult GhcSession = HscEnvEq
155+
156+
-- | A GHC session preloaded with all the dependencies
157+
type instance RuleResult GhcSessionDeps = HscEnvEq
158+
159+
-- | A ModSummary that has enough information to be used to get .hi and .hie files.
160+
type instance RuleResult GetModSummary = ModSummary
161+
```
162+
163+
The `use` family of combinators allow to request rule results. For example, the following code is used in the Eval plugin to request a GHC session and a module summary (for the imports) in order to set up an interactive evaluation environment
164+
```haskell
165+
let nfp = toNormalizedFilePath' fp
166+
session <- runAction "runEvalCmd.ghcSession" state $ use_ GhcSessionDeps nfp
167+
ms <- runAction "runEvalCmd.getModSummary" state $ use_ GetModSummary nfp
168+
```
169+
170+
There are three flavours of `use` combinators:
171+
172+
1. `use*` combinators block and propagate errors,
173+
2. `useWithStale*` combinators block and switch to stale data in case of error,
174+
3. `useWithStaleFast*` combinators return immediately with stale data if any, or block otherwise.
175+
176+
## LSP abstractions
177+
178+
If you have used VSCode or any other LSP editor you are probably already familiar with the capabilities afforded by LSP. If not, check the [specification](https://microsoft.github.io/language-server-protocol/specification) for the full details.
179+
Another good source of information is the [haskell-lsp-types](https://hackage.haskell.org/package/haskell-lsp-types) package, which contains a Haskell encoding of the protocol.
180+
181+
The [haskell-lsp-types](https://hackage.haskell.org/package/haskell-lsp-types-0.22.0.0/docs/Language-Haskell-LSP-Types.html#t:CodeLens) package encodes code lenses in Haskell as:
182+
```haskell
183+
data CodeLens =
184+
CodeLens
185+
{ _range :: Range
186+
, _command :: Maybe Command
187+
, _xdata :: Maybe A.Value
188+
} deriving (Read,Show,Eq)
189+
```
190+
That is, a code lens is a triple of a source range, maybe a command, and optionally some extra data. The [specification](https://microsoft.github.io/language-server-protocol/specification#textDocument_codeLens) clarifies the optionality:
191+
```
192+
/**
193+
* A code lens represents a command that should be shown along with
194+
* source text, like the number of references, a way to run tests, etc.
195+
*
196+
* A code lens is _unresolved_ when no command is associated to it. For performance
197+
* reasons the creation of a code lens and resolving should be done in two stages.
198+
*/
199+
```
200+
201+
To keep things simple our plugin won't make use of the unresolved facility, embedding the command directly in the code lens.
202+
203+
## The explicit imports plugin
204+
205+
To provide code lenses, our plugin must define a code lens provider as well as a Command handler.
206+
The code at `Ide.Plugin.Example` shows how the convenience `defaultPluginDescriptor` function is used
207+
to bootstrap the plugin and how to add the desired providers:
208+
209+
```haskell
210+
descriptor :: PluginId -> PluginDescriptor
211+
descriptor plId = (defaultPluginDescriptor plId) {
212+
-- This plugin provides code lenses
213+
pluginCodeLensProvider = Just provider,
214+
-- This plugin provides a command handler
215+
pluginCommands = [ importLensCommand ]
216+
}
217+
```
218+
219+
### The command handler
220+
221+
Our plugin provider has two components that need to be fleshed out. Let's start with the command provider, since it's the simplest of the two.
222+
223+
```haskell
224+
importLensCommand :: PluginCommand
225+
```
226+
227+
`PluginCommand` is a type synonym defined in `LSP.Types` as:
228+
229+
```haskell
230+
data PluginCommand = forall a. (FromJSON a) =>
231+
PluginCommand { commandId :: CommandId
232+
, commandDesc :: T.Text
233+
, commandFunc :: CommandFunction a
234+
}
235+
```
236+
237+
The meat is in the `commandFunc` field, which is of type `CommandFunction`, another type synonym from `LSP.Types`:
238+
```haskell
239+
type CommandFunction a =
240+
LSP.LspFuncs Config
241+
-> IdeState
242+
-> a
243+
-> IO (Either ResponseError Value, Maybe (ServerMethod, ApplyWorkspaceEditParams))
244+
```
245+
246+
`CommandFunction` takes in the familiar `LspFuncs` and `IdeState` arguments, together with a JSON encoded argument.
247+
I recommend checking the LSP spec in order to understand how commands work, but briefly the LSP server (us) initially sends a command descriptor to the client, in this case as part of a code lens. When the client decides to execute the command on behalf of a user action (in this case a click on the code lens), the client sends this descriptor back to the LSP server which then proceeds to handle and execute the command. The latter part is implemented by the `commandFunc` field of our `PluginCommand` value.
248+
249+
For our command, we are going to have a very simple handler that receives a diff (`WorkspaceEdit`) and returns it to the client. The diff will be generated by our code lens provider and sent as part
250+
of the code lens to the LSP client, who will send it back to our command handler when the user activates
251+
the code lens:
252+
```haskell
253+
importCommandId :: CommandId
254+
importCommandId = "ImportLensCommand"
255+
256+
importLensCommand :: PluginCommand
257+
importLensCommand =
258+
PluginCommand importCommandId "Explicit import command" runImportCommand
259+
260+
-- | The type of the parameters accepted by our command
261+
data ImportCommandParams = ImportCommandParams WorkspaceEdit
262+
deriving Generic
263+
deriving anyclass (FromJSON, ToJSON)
264+
265+
-- | The actual command handler
266+
runImportCommand :: CommandFunction ImportCommandParams
267+
runImportCommand _lspFuncs _state (ImportCommandParams edit) = do
268+
return (Right Null, Just (WorkspaceApplyEdit, ApplyWorkspaceEditParams edit))
269+
270+
```
271+
272+
### The code lens provider
273+
274+
The code lens provider implements all the steps of the algorithm described earlier:
275+
276+
> 1. Request the type checking artefacts from the ghcide subsystem
277+
> 2. Extract the actual import lists from the type checked AST,
278+
> 3. Ask GHC to produce the minimal import lists for this AST,
279+
> 4. For every import statement without a explicit import list, find out what's the minimal import list, and produce a code lens to display it together with a diff to graft the import list in.
280+
281+
The provider takes the usual `LspFuncs` and `IdeState` argument, as well as a `CodeLensParams` value containing the URI
282+
for a file, and returns an IO action producing either an error or a list of code lenses for that file.
283+
284+
```haskell
285+
provider :: CodeLensProvider
286+
provider _lspFuncs -- LSP functions, not used
287+
state -- ghcide state, used to retrieve typechecking artifacts
288+
pId -- plugin Id
289+
CodeLensParams{_textDocument = TextDocumentIdentifier{_uri}}
290+
-- VSCode uses URIs instead of file paths
291+
-- haskell-lsp provides conversion functions
292+
| Just nfp <- uriToNormalizedFilePath $ toNormalizedUri _uri
293+
= do
294+
-- Get the typechecking artifacts from the module
295+
tmr <- runAction "importLens" state $ use TypeCheck nfp
296+
-- We also need a GHC session with all the dependencies
297+
hsc <- runAction "importLens" state $ use GhcSessionDeps nfp
298+
-- Use the GHC api to extract the "minimal" imports
299+
(imports, mbMinImports) <- extractMinimalImports hsc tmr
300+
301+
case mbMinImports of
302+
Just minImports -> do
303+
let minImportsMap =
304+
Map.fromList [ (srcSpanStart l, i) | L l i <- minImports ]
305+
lenses <- forM imports $
306+
-- for every import, maybe generate a code lens
307+
generateLens pId _uri minImportsMap
308+
return $ Right (List $ catMaybes lenses)
309+
_ ->
310+
return $ Right (List [])
311+
| otherwise
312+
= return $ Right (List [])
313+
```
314+
315+
Note how simple it is to retrieve the type checking artifacts for the module as well as a fully setup Ghc session via the Ghcide rules.
316+
317+
The function `extractMinimalImports` extracts the import statements from the AST and generates the minimal import lists, implementing steps 2 and 3 of the algorithm.
318+
The details of the GHC api are not relevant to this tutorial, but the code is terse and easy to read:
319+
320+
```haskell
321+
extractMinimalImports
322+
:: Maybe HscEnvEq
323+
-> Maybe TcModuleResult
324+
-> IO ([LImportDecl GhcRn], Maybe [LImportDecl GhcRn])
325+
extractMinimalImports (Just hsc)) (Just (tmrModule -> TypecheckedModule{..})) = do
326+
-- extract the original imports and the typechecking environment
327+
let (tcEnv,_) = tm_internals_
328+
Just (_, imports, _, _) = tm_renamed_source
329+
ParsedModule{ pm_parsed_source = L loc _} = tm_parsed_module
330+
span = fromMaybe (error "expected real") $ realSpan loc
331+
332+
-- GHC is secretly full of mutable state
333+
gblElts <- readIORef (tcg_used_gres tcEnv)
334+
335+
let usage = findImportUsage imports gblElts
336+
(_, minimalImports) <-
337+
-- getMinimalImports computes the minimal explicit import lists
338+
initTcWithGbl (hscEnv hsc) tcEnv span $ getMinimalImports usage
339+
return (imports, minimalImports)
340+
extractMinimalImports _ _ = return ([], Nothing)
341+
```
342+
343+
The function `generateLens` implements the last piece of the algorithm, step 4, producing a code lens for an import statement that lacks an import list. Note how the code lens includes an `ImportCommandParams` value
344+
that contains a workspace edit that rewrites the import statement, as expected by our command provider.
345+
346+
```haskell
347+
-- | Given an import declaration, generate a code lens unless it has an explicit import list
348+
generateLens :: PluginId
349+
-> Uri
350+
-> Map SrcLoc (ImportDecl GhcRn)
351+
-> LImportDecl GhcRn
352+
-> IO (Maybe CodeLens)
353+
generateLens pId uri minImports (L src imp)
354+
-- Explicit import list case
355+
| ImportDecl{ideclHiding = Just (False,_)} <- imp
356+
= return Nothing
357+
-- No explicit import list
358+
| RealSrcSpan l <- src
359+
, Just explicit <- Map.lookup (srcSpanStart src) minImports
360+
, L _ mn <- ideclName imp
361+
-- (almost) no one wants to see an explicit import list for Prelude
362+
, mn /= moduleName pRELUDE
363+
= do
364+
-- The title of the command is just the minimal explicit import decl
365+
let title = T.pack $ prettyPrint explicit
366+
-- the range of the code lens is the span of the original import decl
367+
_range :: Range = realSrcSpanToRange l
368+
-- the code lens has no extra data
369+
_xdata = Nothing
370+
-- an edit that replaces the whole declaration with the explicit one
371+
edit = WorkspaceEdit (Just editsMap) Nothing
372+
editsMap = HashMap.fromList [(uri, List [importEdit])]
373+
importEdit = TextEdit _range title
374+
-- the command argument is simply the edit
375+
_arguments = Just [toJSON $ ImportCommandParams edit]
376+
-- create the command
377+
_command <- Just <$> mkLspCommand pId importCommandId title _arguments
378+
-- create and return the code lens
379+
return $ Just CodeLens{..}
380+
| otherwise
381+
= return Nothing
382+
```
383+
384+
## Wrapping up
385+
386+
There's only one code change left to do at this point: "link" the plugin in the `Main` HLS module.
387+
388+
The full code as used in this tutorial, including imports, can be found in [this Gist](https://gist.github.com/pepeiborra/49b872b2e9ad112f61a3220cdb7db967) as well as in this [branch](https://github.com/pepeiborra/ide/blob/imports-lens/src/Ide/Plugin/ImportLens.hs)
389+
390+
I hope this has given you a taste of how easy and joyful it is to write plugins for HLS.
391+
If you are looking for ideas for contributing, here are some cool ones found in the HLS issue tracker:
392+
- [#205](https://github.com/haskell/haskell-language-server/issues/205) Integrate code synthesis tools (djinn, hoogle+)
393+
- [#258](https://github.com/haskell/haskell-language-server/issues/258) Integration with [Stan](https://github.com/kowainik/stan)
394+
- [#282](https://github.com/haskell/haskell-language-server/issues/282) High-level refactorings (rename, move, extract)
395+
- [#323](https://github.com/haskell/haskell-language-server/issues/323) Case splitting

docs/settings-vscode.png

130 KB
Loading

0 commit comments

Comments
 (0)