Skip to content

Commit 7ec5b7d

Browse files
committed
Compile plugin-tutorial using markdown-unlit
Makes sure the plugin-tutorial can never be out-of-date again.
1 parent 776301a commit 7ec5b7d

File tree

5 files changed

+145
-61
lines changed

5 files changed

+145
-61
lines changed

docs/contributing/plugin-tutorial.lhs

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1 @@
1+
plugin-tutorial.md

docs/contributing/plugin-tutorial.md

Lines changed: 124 additions & 59 deletions
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,5 @@
11
# Let’s write a Haskell Language Server plugin
2+
23
Originally written by Pepe Iborra, maintained by the Haskell community.
34

45
Haskell Language Server (HLS) is a Language Server Protocol (LSP) server for the Haskell programming language. It builds on several previous efforts to create a Haskell IDE.
@@ -22,6 +23,49 @@ While writing them, I didn't have to worry about performance, UI, or distributio
2223

2324
The plugins also make these tools much more accessible to all users of HLS.
2425

26+
## Preamble
27+
28+
```haskell
29+
{-# LANGUAGE OverloadedStrings #-}
30+
{-# LANGUAGE DerivingStrategies #-}
31+
{-# LANGUAGE ScopedTypeVariables #-}
32+
{-# LANGUAGE RecordWildCards #-}
33+
{-# LANGUAGE NamedFieldPuns #-}
34+
{-# LANGUAGE ViewPatterns #-}
35+
{-# LANGUAGE DeriveGeneric #-}
36+
{-# LANGUAGE DataKinds #-}
37+
{-# LANGUAGE DeriveAnyClass #-}
38+
39+
import Ide.Types
40+
import Ide.Logger
41+
import Ide.Plugin.Error
42+
43+
import Development.IDE.Core.RuleTypes
44+
import Development.IDE.Core.Service hiding (Log)
45+
import Development.IDE.Core.Shake hiding (Log)
46+
import Development.IDE.GHC.Compat
47+
import Development.IDE.GHC.Compat.Core
48+
import Development.IDE.GHC.Error
49+
import Development.IDE.Types.HscEnvEq
50+
import Development.IDE.Core.PluginUtils
51+
52+
import qualified Language.LSP.Server as LSP
53+
import Language.LSP.Protocol.Types as JL
54+
import Language.LSP.Protocol.Message
55+
56+
import Data.Aeson as Aeson
57+
import Data.Map (Map)
58+
import Data.IORef
59+
import Data.Maybe (fromMaybe, catMaybes)
60+
import qualified Data.Map as Map
61+
import qualified Data.HashMap.Strict as HashMap
62+
import qualified Data.Text as T
63+
import Control.Monad (forM)
64+
import Control.Monad.IO.Class (liftIO)
65+
import Control.Monad.Trans.Class
66+
import GHC.Generics (Generic)
67+
```
68+
2569
## Plugins in the HLS codebase
2670

2771
The HLS codebase includes several plugins (found in `./plugins`). For example:
@@ -37,7 +81,9 @@ I recommend looking at the existing plugins for inspiration and reference. A few
3781
- Folders containing the plugin follow the `hls-pluginname-plugin` naming convention
3882
- Plugins are "linked" in `src/HlsPlugins.hs#idePlugins`. New plugin descriptors
3983
must be added there.
40-
```haskell -- src/HlsPlugins.hs
84+
85+
```haskell ignore
86+
-- Defined in src/HlsPlugins.**hs**
4187

4288
idePlugins = pluginDescToIdePlugins allPlugins
4389
where
@@ -53,6 +99,7 @@ I recommend looking at the existing plugins for inspiration and reference. A few
5399
, NewPlugin.descriptor "new-plugin" -- Add new plugins here.
54100
]
55101
```
102+
56103
To add a new plugin, extend the list of `allPlugins` and rebuild.
57104

58105
## The goal of the plugin we will write
@@ -80,7 +127,7 @@ Once the build is done, you can find the location of the HLS binary with `cabal
80127
This way you can simply test your changes by reloading your editor after rebuilding the binary.
81128

82129
> **Note:** In VSCode, edit the "Haskell Server Executable Path" setting.
83-
130+
>
84131
> **Note:** In Emacs, edit the `lsp-haskell-server-path` variable.
85132
86133
![Settings](settings-vscode.png)
@@ -90,6 +137,7 @@ This way you can simply test your changes by reloading your editor after rebuild
90137
## Digression about the Language Server Protocol
91138

92139
There are two main types of communication in the Language Server Protocol:
140+
93141
- A **request-response interaction** type where one party sends a message that requires a response from the other party.
94142
- A **notification** is a one-way interaction where one party sends a message without expecting any response.
95143

@@ -98,24 +146,27 @@ There are two main types of communication in the Language Server Protocol:
98146
## Anatomy of a plugin
99147

100148
HLS plugins are values of the `PluginDescriptor` datatype, which is defined in `hls-plugin-api/src/Ide/Types.hs` as:
101-
```haskell
149+
150+
```haskell ignore
102151
data PluginDescriptor (ideState :: Type) =
103152
PluginDescriptor { pluginId :: !PluginId
104153
, pluginCommands :: ![PluginCommand ideState]
105154
, pluginHandlers :: PluginHandlers ideState
106155
, pluginNotificationHandlers :: PluginNotificationHandlers ideState
107-
, [...] -- Other fields omitted for brevity.
156+
-- , [...] -- Other fields omitted for brevity.
108157
}
109158
```
110159

111160
### Request-response interaction
112161

113162
The `pluginHandlers` handle LSP client requests and provide responses to the client. They must fulfill these requests as quickly as possible.
163+
114164
- Example: When you want to format a file, the client sends the [`textDocument/formatting`](https://microsoft.github.io/language-server-protocol/specifications/lsp/3.17/specification/#textDocument_formatting) request to the server. The server formats the file and responds with the formatted content.
115165

116166
### Notification
117167

118168
The `pluginNotificationHandlers` handle notifications sent by the client to the server that are not explicitly triggered by a user.
169+
119170
- Example: Whenever you modify a Haskell file, the client sends a notification informing HLS about the changes to the file.
120171

121172
The `pluginCommands` are special types of user-initiated notifications sent to
@@ -124,6 +175,7 @@ the server. These actions can be long-running and involve multiple modules.
124175
## The explicit imports plugin
125176

126177
To achieve our plugin goals, we need to define:
178+
127179
- a command handler (`importLensCommand`),
128180
- a code lens request handler (`lensProvider`).
129181

@@ -134,13 +186,15 @@ Using the convenience `defaultPluginDescriptor` function, we can bootstrap the p
134186
```haskell
135187
-- plugins/hls-explicit-imports-plugin/src/Ide/Plugin/ExplicitImports.hs
136188

189+
data Log
190+
137191
-- | The "main" function of a plugin.
138192
descriptor :: Recorder (WithPriority Log) -> PluginId -> PluginDescriptor IdeState
139193
descriptor recorder plId =
140-
(defaultPluginDescriptor plId)
194+
(defaultPluginDescriptor plId "A plugin for generating the minimal imports")
141195
{ pluginCommands = [importLensCommand], -- The plugin provides a command handler
142196
pluginHandlers = mconcat -- The plugin provides request handlers
143-
[ lensProvider
197+
[ mkPluginHandler SMethod_TextDocumentCodeLens provider
144198
]
145199
}
146200
```
@@ -150,14 +204,15 @@ We'll start with the command, since it's the simplest of the two.
150204
### The command handler
151205

152206
In short, LSP commands work like this:
207+
153208
- The LSP server (HLS) initially sends a command descriptor to the client, in this case as part of a code lens.
154209
- When the user clicks on the code lens, the client asks HLS to execute the command with the given descriptor. The server then handles and executes the command; this latter part is implemented by the `commandFunc` field of our `PluginCommand` value.
155210

156211
> **Note**: Check the [LSP spec](https://microsoft.github.io/language-server-protocol/specification) for a deeper understanding of how commands work.
157212
158213
The command handler will be called `importLensCommand` and have the `PluginCommand` type, a type defined in `Ide.Types` as:
159214

160-
```haskell
215+
```haskell ignore
161216
-- hls-plugin-api/src/Ide/Types.hs
162217

163218
data PluginCommand ideState = forall a. (FromJSON a) =>
@@ -174,18 +229,23 @@ Let's start by creating an unfinished command handler. We'll give it an ID and a
174229
importLensCommand :: PluginCommand IdeState
175230
importLensCommand =
176231
PluginCommand
177-
{ commandId = "ImportLensCommand"
232+
{ commandId = importCommandId
178233
, commandDesc = "Explicit import command"
179234
, commandFunc = runImportCommand
180235
}
181236

237+
importCommandId :: CommandId
238+
importCommandId = "ImportLensCommand"
239+
```
240+
241+
```haskell ignore
182242
-- | Not implemented yet.
183243
runImportCommand = undefined
184244
```
185245

186246
The most important (and still `undefined`) field is `commandFunc :: CommandFunction`, a type synonym from `LSP.Types`:
187247

188-
```haskell
248+
```haskell ignore
189249
-- hls-plugin-api/src/Ide/Types.hs
190250

191251
type CommandFunction ideState a
@@ -194,8 +254,7 @@ type CommandFunction ideState a
194254
-> LspM Config (Either ResponseError Value)
195255
```
196256

197-
198-
`CommandFunction` takes an `ideState` and a JSON-encodable argument. `LspM` is a monad transformer with access to IO, and having access to a language context environment `Config`. The action evaluates to an `Either` value. `Left` indicates failure with a `ResponseError`, `Right` indicates success with a `Value`.
257+
`CommandFunction` takes an `ideState` and a JSON-encodable argument. `LspM` is a monad transformer with access to IO, and having access to a language context environment `Config`. The action evaluates to an `Either` value. `Left` indicates failure with a `ResponseError`, `Right` indicates sucess with a `Value`.
199258

200259
Our handler will ignore the state argument and only use the `WorkspaceEdit` argument.
201260

@@ -207,10 +266,10 @@ newtype ImportCommandParams = ImportCommandParams WorkspaceEdit
207266

208267
-- | The actual command handler
209268
runImportCommand :: CommandFunction IdeState ImportCommandParams
210-
runImportCommand _ (ImportCommandParams edit) = do
269+
runImportCommand _ _ (ImportCommandParams edit) = do
211270
-- This command simply triggers a workspace edit!
212-
_ <- sendRequest SWorkspaceApplyEdit (ApplyWorkspaceEditParams Nothing edit) (\_ -> pure ())
213-
return (Right Null)
271+
_ <- lift $ pluginSendRequest SMethod_WorkspaceApplyEdit (ApplyWorkspaceEditParams Nothing edit) (\_ -> pure ())
272+
return $ InR JL.Null
214273
```
215274

216275
`runImportCommand` [sends a request](https://hackage.haskell.org/package/lsp/docs/Language-LSP-Server.html#v:sendRequest) to the client using the method `SWorkspaceApplyEdit` and the parameters `ApplyWorkspaceEditParams Nothing edit`, providing a response handler that does nothing. It then returns `Right Null`, which is an empty `Aeson.Value` wrapped in `Right`.
@@ -219,42 +278,41 @@ runImportCommand _ (ImportCommandParams edit) = do
219278

220279
The code lens provider implements all the steps of the algorithm described earlier:
221280

222-
> 1. Request the type checking artifacts.
223-
> 2. Extract the actual import lists from the type-checked AST.
224-
> 3. Ask GHC to produce the minimal import lists for this AST.
225-
> 4. For each import statement lacking an explicit list, determine its minimal import list and generate a code lens displaying this list along with a command to insert it.
281+
> 1. Request the type checking artifacts.
282+
> 2. Extract the actual import lists from the type-checked AST.
283+
> 3. Ask GHC to produce the minimal import lists for this AST.
284+
> 4. For each import statement lacking an explicit list, determine its minimal import list and generate a code lens displaying this list along with a command to insert it.
226285
227286
The provider takes the usual `LspFuncs` and `IdeState` arguments, as well as a `CodeLensParams` value containing a file URI. It returns an IO action that produces either an error or a list of code lenses for that file.
228287

229288
```haskell
230-
provider :: CodeLensProvider
231-
provider _lspFuncs -- LSP functions, not used
232-
state -- ghcide state, used to retrieve typechecking artifacts
289+
provider :: PluginMethodHandler IdeState Method_TextDocumentCodeLens
290+
provider state -- ghcide state, used to retrieve typechecking artifacts
233291
pId -- Plugin ID
234-
CodeLensParams{_textDocument = TextDocumentIdentifier{_uri}}
292+
CodeLensParams{_textDocument = TextDocumentIdentifier{_uri}} = do
235293
-- VSCode uses URIs instead of file paths
236294
-- haskell-lsp provides conversion functions
237-
| Just nfp <- uriToNormalizedFilePath $ toNormalizedUri _uri
238-
= do
239-
-- Get the typechecking artifacts from the module
240-
tmr <- runAction "importLens" state $ use TypeCheck nfp
241-
-- We also need a GHC session with all the dependencies
242-
hsc <- runAction "importLens" state $ use GhcSessionDeps nfp
243-
-- Use the GHC API to extract the "minimal" imports
244-
(imports, mbMinImports) <- extractMinimalImports hsc tmr
245-
246-
case mbMinImports of
247-
Just minImports -> do
248-
let minImportsMap =
249-
Map.fromList [ (srcSpanStart l, i) | L l i <- minImports ]
250-
lenses <- forM imports $
251-
-- for every import, maybe generate a code lens
252-
generateLens pId _uri minImportsMap
253-
return $ Right (List $ catMaybes lenses)
254-
_ ->
255-
return $ Right (List [])
256-
| otherwise
257-
= return $ Right (List [])
295+
nfp <- getNormalizedFilePathE _uri
296+
-- Get the typechecking artifacts from the module
297+
tmr <- runActionE "importLens" state $ useE TypeCheck nfp
298+
-- We also need a GHC session with all the dependencies
299+
hsc <- runActionE "importLens" state $ useE GhcSessionDeps nfp
300+
-- Use the GHC API to extract the "minimal" imports
301+
(imports, mbMinImports) <- liftIO $ extractMinimalImports hsc tmr
302+
303+
case mbMinImports of
304+
Just minImports -> do
305+
let minImportsMap =
306+
Map.fromList [ (realSrcLocToPosition loc, i)
307+
| L l i <- minImports
308+
, let RealSrcLoc loc _ = srcSpanStart (locA l)
309+
]
310+
lenses <- forM imports $ \imp ->
311+
-- for every import, maybe generate a code lens
312+
liftIO (generateLens pId _uri minImportsMap imp)
313+
return $ InL (catMaybes lenses)
314+
_ ->
315+
return $ InL []
258316
```
259317

260318
Note the simplicity of retrieving the type checking artifacts for the module, as well as a fully set up GHC session, via the `ghcide` rules.
@@ -265,14 +323,14 @@ The details of the GHC API are not relevant to this tutorial, but the code is te
265323

266324
```haskell
267325
extractMinimalImports
268-
:: Maybe HscEnvEq
269-
-> Maybe TcModuleResult
326+
:: HscEnvEq
327+
-> TcModuleResult
270328
-> IO ([LImportDecl GhcRn], Maybe [LImportDecl GhcRn])
271-
extractMinimalImports (Just hsc)) (Just (tmrModule -> TypecheckedModule{..})) = do
329+
extractMinimalImports hsc TcModuleResult{..} = do
272330
-- Extract the original imports and the typechecking environment
273-
let (tcEnv,_) = tm_internals_
274-
Just (_, imports, _, _) = tm_renamed_source
275-
ParsedModule{ pm_parsed_source = L loc _} = tm_parsed_module
331+
let tcEnv = tmrTypechecked
332+
(_, imports, _, _) = tmrRenamed
333+
ParsedModule{ pm_parsed_source = L loc _} = tmrParsed
276334
span = fromMaybe (error "expected real") $ realSpan loc
277335

278336
-- GHC is secretly full of mutable state
@@ -283,7 +341,6 @@ extractMinimalImports (Just hsc)) (Just (tmrModule -> TypecheckedModule{..})) =
283341
-- getMinimalImports computes the minimal explicit import lists
284342
initTcWithGbl (hscEnv hsc) tcEnv span $ getMinimalImports usage
285343
return (imports, minimalImports)
286-
extractMinimalImports _ _ = return ([], Nothing)
287344
```
288345

289346
The function `generateLens` implements step 4 of the algorithm, producing a code lens for an import statement that lacks an import list. The code lens includes an `ImportCommandParams` value containing a workspace edit that rewrites the import statement, as our command provider expects.
@@ -292,34 +349,36 @@ The function `generateLens` implements step 4 of the algorithm, producing a code
292349
-- | Given an import declaration, generate a code lens unless it has an explicit import list
293350
generateLens :: PluginId
294351
-> Uri
295-
-> Map SrcLoc (ImportDecl GhcRn)
352+
-> Map Position (ImportDecl GhcRn)
296353
-> LImportDecl GhcRn
297354
-> IO (Maybe CodeLens)
298355
generateLens pId uri minImports (L src imp)
299356
-- Explicit import list case
300-
| ImportDecl{ideclHiding = Just (False,_)} <- imp
357+
| ImportDecl{ideclImportList = Just _} <- imp
301358
= return Nothing
302359
-- No explicit import list
303-
| RealSrcSpan l <- src
304-
, Just explicit <- Map.lookup (srcSpanStart src) minImports
360+
| RealSrcSpan l _ <- locA src
361+
, let position = realSrcLocToPosition $ realSrcSpanStart l
362+
, Just explicit <- Map.lookup position minImports
305363
, L _ mn <- ideclName imp
306364
-- (Almost) no one wants to see an explicit import list for Prelude
307365
, mn /= moduleName pRELUDE
308366
= do
309367
-- The title of the command is just the minimal explicit import decl
310-
let title = T.pack $ prettyPrint explicit
368+
let title = T.pack $ printWithoutUniques explicit
311369
-- The range of the code lens is the span of the original import decl
312370
_range :: Range = realSrcSpanToRange l
313371
-- The code lens has no extra data
314372
_xdata = Nothing
315373
-- An edit that replaces the whole declaration with the explicit one
316-
edit = WorkspaceEdit (Just editsMap) Nothing
317-
editsMap = HashMap.fromList [(uri, List [importEdit])]
374+
edit = WorkspaceEdit (Just editsMap) Nothing Nothing
375+
editsMap = Map.fromList [(uri, [importEdit])]
318376
importEdit = TextEdit _range title
319377
-- The command argument is simply the edit
320378
_arguments = Just [toJSON $ ImportCommandParams edit]
321-
-- Create the command
322-
_command <- Just <$> mkLspCommand pId importCommandId title _arguments
379+
_data_ = Nothing
380+
-- Create the command
381+
_command = Just $ mkLspCommand pId importCommandId title _arguments
323382
-- Create and return the code lens
324383
return $ Just CodeLens{..}
325384
| otherwise
@@ -333,6 +392,7 @@ There's only one Haskell code change left to do at this point: "link" the plugin
333392
Integrating the plugin into HLS itself requires changes to several configuration files.
334393

335394
A good approach is to search for the ID of an existing plugin (e.g., `hls-class-plugin`):
395+
336396
- `./cabal*.project` and `./stack*.yaml`: Add the plugin package to the `packages` field.
337397
- `./haskell-language-server.cabal`: Add a conditional block with the plugin package dependency.
338398
- `./.github/workflows/test.yml`: Add a block to run the plugin's test suite.
@@ -342,3 +402,8 @@ A good approach is to search for the ID of an existing plugin (e.g., `hls-class-
342402
The full code used in this tutorial, including imports, is available in [this Gist](https://gist.github.com/pepeiborra/49b872b2e9ad112f61a3220cdb7db967) and in this [branch](https://github.com/pepeiborra/ide/blob/imports-lens/src/Ide/Plugin/ImportLens.hs).
343403

344404
I hope this has given you a taste of how easy and joyful it is to write plugins for HLS. If you are looking for contribution ideas, here are some good ones listed in the HLS [issue tracker](https://github.com/haskell/haskell-language-server/issues).
405+
406+
```haskell
407+
main :: IO ()
408+
main = putStrLn "Just here to silence the error!"
409+
```

ghcide/src/Development/IDE/GHC/Compat/Core.hs

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -225,6 +225,7 @@ module Development.IDE.GHC.Compat.Core (
225225
SrcLoc.noSrcSpan,
226226
SrcLoc.noSrcLoc,
227227
SrcLoc.noLoc,
228+
SrcLoc.srcSpanToRealSrcSpan,
228229
mapLoc,
229230
-- * Finder
230231
FindResult(..),

0 commit comments

Comments
 (0)