Skip to content

Commit 25aa3db

Browse files
committed
Add symbols provider to plugin support
1 parent e473612 commit 25aa3db

File tree

8 files changed

+128
-11
lines changed

8 files changed

+128
-11
lines changed

src/Ide/Plugin.hs

Lines changed: 45 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -15,6 +15,7 @@ module Ide.Plugin
1515
, allLspCmdIds
1616
, allLspCmdIds'
1717
, getPid
18+
, responseError
1819
) where
1920

2021
import Control.Lens ( (^.) )
@@ -59,6 +60,7 @@ asGhcIdePlugin mp =
5960
-- Note: diagnostics are provided via Rules from pluginDiagnosticProvider
6061
mkPlugin hoverPlugins pluginHoverProvider <>
6162
-- TODO: symbols via pluginSymbolProvider
63+
mkPlugin symbolsPlugin pluginSymbolsProvider <>
6264
mkPlugin formatterPlugins pluginFormattingProvider
6365
-- TODO: completions
6466
where
@@ -401,6 +403,49 @@ makeHover hps _lf ideState params
401403
-- ---------------------------------------------------------------------
402404
-- ---------------------------------------------------------------------
403405

406+
symbolsPlugin :: [(PluginId, SymbolsProvider)] -> Plugin Config
407+
symbolsPlugin hs = Plugin symbolsRules (symbolsHandlers hs)
408+
409+
symbolsRules :: Rules ()
410+
symbolsRules = mempty
411+
412+
symbolsHandlers :: [(PluginId, SymbolsProvider)] -> PartialHandlers Config
413+
symbolsHandlers hps = PartialHandlers $ \WithMessage{..} x ->
414+
return x {LSP.documentSymbolHandler = withResponse RspDocumentSymbols (makeSymbols hps)}
415+
416+
makeSymbols :: [(PluginId, SymbolsProvider)]
417+
-> LSP.LspFuncs Config
418+
-> IdeState
419+
-> DocumentSymbolParams
420+
-> IO (Either ResponseError DSResult)
421+
makeSymbols sps lf ideState params
422+
= do
423+
let uri' = params ^. textDocument . uri
424+
(C.ClientCapabilities _ tdc _ _) = LSP.clientCapabilities lf
425+
supportsHierarchy = fromMaybe False $ tdc >>= C._documentSymbol
426+
>>= C._hierarchicalDocumentSymbolSupport
427+
convertSymbols :: [DocumentSymbol] -> DSResult
428+
convertSymbols symbs
429+
| supportsHierarchy = DSDocumentSymbols $ List symbs
430+
| otherwise = DSSymbolInformation (List $ concatMap (go Nothing) symbs)
431+
where
432+
go :: Maybe T.Text -> DocumentSymbol -> [SymbolInformation]
433+
go parent ds =
434+
let children' :: [SymbolInformation]
435+
children' = concatMap (go (Just name')) (fromMaybe mempty (ds ^. children))
436+
loc = Location uri' (ds ^. range)
437+
name' = ds ^. name
438+
si = SymbolInformation name' (ds ^. kind) (ds ^. deprecated) loc parent
439+
in [si] <> children'
440+
441+
mhs <- mapM (\(_,p) -> p ideState params) sps
442+
case rights mhs of
443+
[] -> return $ Left $ responseError $ T.pack $ show $ lefts mhs
444+
hs -> return $ Right $ convertSymbols $ concat hs
445+
446+
-- ---------------------------------------------------------------------
447+
-- ---------------------------------------------------------------------
448+
404449
formatterPlugins :: [(PluginId, FormattingProvider IO)] -> Plugin Config
405450
formatterPlugins providers
406451
= Plugin formatterRules

src/Ide/Plugin/Example.hs

Lines changed: 19 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -48,8 +48,8 @@ descriptor plId = PluginDescriptor
4848
, pluginCodeActionProvider = Just codeAction
4949
, pluginCodeLensProvider = Just codeLens
5050
, pluginDiagnosticProvider = Nothing
51-
, pluginHoverProvider = Just hover
52-
, pluginSymbolProvider = Nothing
51+
, pluginHoverProvider = Just hover
52+
, pluginSymbolsProvider = Just symbols
5353
, pluginFormattingProvider = Nothing
5454
, pluginCompletionProvider = Nothing
5555
}
@@ -201,3 +201,20 @@ logAndRunRequest label getResults ide pos path = do
201201
label <> " request at position " <> T.pack (showPosition pos) <>
202202
" in file: " <> T.pack path
203203
runAction ide $ getResults filePath pos
204+
205+
-- ---------------------------------------------------------------------
206+
207+
symbols :: SymbolsProvider
208+
symbols _ide (DocumentSymbolParams _doc _mt)
209+
= pure $ Right [r]
210+
where
211+
r = DocumentSymbol name detail kind deprecation range selR chList
212+
name = "Example_symbol_name"
213+
detail = Nothing
214+
kind = SkVariable
215+
deprecation = Nothing
216+
range = Range (Position 2 0) (Position 2 5)
217+
selR = range
218+
chList = Nothing
219+
220+
-- ---------------------------------------------------------------------

src/Ide/Plugin/Example2.hs

Lines changed: 19 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -48,8 +48,8 @@ descriptor plId = PluginDescriptor
4848
, pluginCodeActionProvider = Just codeAction
4949
, pluginCodeLensProvider = Just codeLens
5050
, pluginDiagnosticProvider = Nothing
51-
, pluginHoverProvider = Just hover
52-
, pluginSymbolProvider = Nothing
51+
, pluginHoverProvider = Just hover
52+
, pluginSymbolsProvider = Just symbols
5353
, pluginFormattingProvider = Nothing
5454
, pluginCompletionProvider = Nothing
5555
}
@@ -198,3 +198,20 @@ logAndRunRequest label getResults ide pos path = do
198198
label <> " request at position " <> T.pack (showPosition pos) <>
199199
" in file: " <> T.pack path
200200
runAction ide $ getResults filePath pos
201+
202+
-- ---------------------------------------------------------------------
203+
204+
symbols :: SymbolsProvider
205+
symbols _ide (DocumentSymbolParams _doc _mt)
206+
= pure $ Right [r]
207+
where
208+
r = DocumentSymbol name detail kind deprecation range selR chList
209+
name = "Example2_symbol_name"
210+
detail = Nothing
211+
kind = SkVariable
212+
deprecation = Nothing
213+
range = Range (Position 4 1) (Position 4 7)
214+
selR = range
215+
chList = Nothing
216+
217+
-- ---------------------------------------------------------------------

src/Ide/Plugin/Floskell.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -34,7 +34,7 @@ descriptor plId = PluginDescriptor
3434
, pluginCodeLensProvider = Nothing
3535
, pluginDiagnosticProvider = Nothing
3636
, pluginHoverProvider = Nothing
37-
, pluginSymbolProvider = Nothing
37+
, pluginSymbolsProvider = Nothing
3838
, pluginFormattingProvider = Just provider
3939
, pluginCompletionProvider = Nothing
4040
}

src/Ide/Plugin/Ormolu.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -42,7 +42,7 @@ descriptor plId = PluginDescriptor
4242
, pluginCodeLensProvider = Nothing
4343
, pluginDiagnosticProvider = Nothing
4444
, pluginHoverProvider = Nothing
45-
, pluginSymbolProvider = Nothing
45+
, pluginSymbolsProvider = Nothing
4646
, pluginFormattingProvider = Just provider
4747
, pluginCompletionProvider = Nothing
4848
}

src/Ide/Plugin/Pragmas.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -32,7 +32,7 @@ descriptor plId = PluginDescriptor
3232
, pluginCodeLensProvider = Nothing
3333
, pluginDiagnosticProvider = Nothing
3434
, pluginHoverProvider = Nothing
35-
, pluginSymbolProvider = Nothing
35+
, pluginSymbolsProvider = Nothing
3636
, pluginFormattingProvider = Nothing
3737
, pluginCompletionProvider = Nothing
3838
}

src/Ide/Types.hs

Lines changed: 5 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -10,6 +10,7 @@ module Ide.Types
1010
, CommandId(..)
1111
, DiagnosticProvider(..)
1212
, DiagnosticProviderFunc(..)
13+
, SymbolsProvider
1314
, FormattingType(..)
1415
, FormattingProvider
1516
, HoverProvider
@@ -51,7 +52,7 @@ data PluginDescriptor =
5152
-- ^ TODO: diagnostics are generally provided via rules,
5253
-- this is probably redundant.
5354
, pluginHoverProvider :: !(Maybe HoverProvider)
54-
, pluginSymbolProvider :: !(Maybe SymbolProvider)
55+
, pluginSymbolsProvider :: !(Maybe SymbolsProvider)
5556
, pluginFormattingProvider :: !(Maybe (FormattingProvider IO))
5657
, pluginCompletionProvider :: !(Maybe CompletionProvider)
5758
}
@@ -122,7 +123,9 @@ data DiagnosticTrigger = DiagnosticOnOpen
122123
-- type HoverProvider = Uri -> Position -> IO (Either ResponseError [Hover])
123124
type HoverProvider = IdeState -> TextDocumentPositionParams -> IO (Either ResponseError (Maybe Hover))
124125

125-
type SymbolProvider = Uri -> IO (Either ResponseError [DocumentSymbol])
126+
type SymbolsProvider = IdeState
127+
-> DocumentSymbolParams
128+
-> IO (Either ResponseError [DocumentSymbol])
126129

127130
type ExecuteCommandProvider = IdeState
128131
-> ExecuteCommandParams

test/functional/PluginSpec.hs

Lines changed: 37 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -3,7 +3,7 @@
33
{-# LANGUAGE TypeApplications #-}
44
module PluginSpec where
55

6-
-- import Control.Applicative.Combinators
6+
import Control.Applicative.Combinators
77
import Control.Lens hiding (List)
88
-- import Control.Monad
99
import Control.Monad.IO.Class
@@ -27,7 +27,7 @@ import TestUtils
2727
-- ---------------------------------------------------------------------
2828

2929
spec :: Spec
30-
spec =
30+
spec = do
3131
describe "composes code actions" $
3232
it "provides 3.8 code actions" $ runSession hieCommandExamplePlugin fullCaps "test/testdata" $ do
3333

@@ -67,3 +67,38 @@ spec =
6767

6868
-- noDiagnostics
6969
return ()
70+
71+
describe "symbol providers" $
72+
it "combines symbol providers" $ runSession hieCommandExamplePlugin fullCaps "test/testdata" $ do
73+
74+
doc <- openDoc "Format.hs" "haskell"
75+
76+
_ <- waitForDiagnostics
77+
78+
id2 <- sendRequest TextDocumentDocumentSymbol (DocumentSymbolParams doc Nothing)
79+
symbolsRsp <- skipManyTill anyNotification message :: Session DocumentSymbolsResponse
80+
liftIO $ symbolsRsp ^. L.id `shouldBe` responseId id2
81+
82+
liftIO $ symbolsRsp ^. L.result `shouldBe`
83+
Just (DSDocumentSymbols
84+
(List [DocumentSymbol
85+
"Example_symbol_name"
86+
Nothing
87+
SkVariable
88+
Nothing
89+
(Range {_start = Position {_line = 2, _character = 0}
90+
, _end = Position {_line = 2, _character = 5}})
91+
(Range {_start = Position {_line = 2, _character = 0}
92+
, _end = Position {_line = 2, _character = 5}})
93+
Nothing
94+
,DocumentSymbol "Example2_symbol_name"
95+
Nothing
96+
SkVariable
97+
Nothing
98+
(Range {_start = Position {_line = 4, _character = 1}
99+
, _end = Position {_line = 4, _character = 7}})
100+
(Range {_start = Position {_line = 4, _character = 1}
101+
, _end = Position {_line = 4, _character = 7}})
102+
Nothing]))
103+
104+
return ()

0 commit comments

Comments
 (0)