forked from haskell/haskell-language-server
-
Notifications
You must be signed in to change notification settings - Fork 1
/
Copy pathGhcIde.hs
76 lines (65 loc) · 3.57 KB
/
GhcIde.hs
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE OverloadedStrings #-}
-- | Exposes the ghcide features as an HLS plugin
module Development.IDE.Plugin.HLS.GhcIde
(
descriptors
, Log(..)
) where
import Control.Monad.IO.Class
import Development.IDE
import Development.IDE.LSP.HoverDefinition
import qualified Development.IDE.LSP.Notifications as Notifications
import Development.IDE.LSP.Outline
import qualified Development.IDE.Plugin.CodeAction as CodeAction
import qualified Development.IDE.Plugin.Completions as Completions
import qualified Development.IDE.Plugin.TypeLenses as TypeLenses
import Ide.Types
import Language.LSP.Server (LspM)
import Language.LSP.Types
import Text.Regex.TDFA.Text ()
data Log
= LogNotifications Notifications.Log
| LogCompletions Completions.Log
| LogTypeLenses TypeLenses.Log
deriving Show
instance Pretty Log where
pretty = \case
LogNotifications log -> pretty log
LogCompletions log -> pretty log
LogTypeLenses log -> pretty log
descriptors :: Recorder (WithPriority Log) -> [PluginDescriptor IdeState]
descriptors recorder =
[ descriptor "ghcide-hover-and-symbols",
CodeAction.iePluginDescriptor "ghcide-code-actions-imports-exports",
CodeAction.typeSigsPluginDescriptor "ghcide-code-actions-type-signatures",
CodeAction.bindingsPluginDescriptor "ghcide-code-actions-bindings",
CodeAction.fillHolePluginDescriptor "ghcide-code-actions-fill-holes",
Completions.descriptor (cmapWithPrio LogCompletions recorder) "ghcide-completions",
TypeLenses.descriptor (cmapWithPrio LogTypeLenses recorder) "ghcide-type-lenses",
Notifications.descriptor (cmapWithPrio LogNotifications recorder) "ghcide-core"
]
-- ---------------------------------------------------------------------
descriptor :: PluginId -> PluginDescriptor IdeState
descriptor plId = (defaultPluginDescriptor plId)
{ pluginHandlers = mkPluginHandler STextDocumentHover hover'
<> mkPluginHandler STextDocumentDocumentSymbol symbolsProvider
<> mkPluginHandler STextDocumentDefinition (\ide _ DefinitionParams{..} ->
gotoDefinition ide TextDocumentPositionParams{..})
<> mkPluginHandler STextDocumentTypeDefinition (\ide _ TypeDefinitionParams{..} ->
gotoTypeDefinition ide TextDocumentPositionParams{..})
<> mkPluginHandler STextDocumentDocumentHighlight (\ide _ DocumentHighlightParams{..} ->
documentHighlight ide TextDocumentPositionParams{..})
<> mkPluginHandler STextDocumentReferences (\ide _ params -> references ide params)
<> mkPluginHandler SWorkspaceSymbol (\ide _ params -> wsSymbols ide params),
pluginConfigDescriptor = defaultConfigDescriptor {configEnableGenericConfig = False}
}
-- ---------------------------------------------------------------------
hover' :: IdeState -> PluginId -> HoverParams -> LspM c (Either ResponseError (Maybe Hover))
hover' ideState _ HoverParams{..} = do
liftIO $ logDebug (ideLogger ideState) "GhcIde.hover entered (ideLogger)" -- AZ
hover ideState TextDocumentPositionParams{..}
-- ---------------------------------------------------------------------
symbolsProvider :: IdeState -> PluginId -> DocumentSymbolParams -> LspM c (Either ResponseError (List DocumentSymbol |? List SymbolInformation))
symbolsProvider ide _ params = moduleOutline ide params
-- ---------------------------------------------------------------------