Skip to content

Commit 2afcaf5

Browse files
committed
Invert the dependency between ghcide and hls-plugin-api
This PR includes changes both to ghcide and HLS to implement the reorg described in https://github.com/haskell/ghcide/issues/936#issuecomment-751437853 To summarise: - `hls-plugin-api` no longer depends on ghcide. - `ghcide` now depends on `hls-plugin-api` and exposes: - The ghcide HLS plugin - The `asGhcIdePlugin` adaptor The goals are: - to be able to break the `ghcide` HLS plugin down - to rewrite exe:ghcide on top of the HLS plugin model. The ghcide side is reviewed in haskell/ghcide#963 If this change is accepted there are two further considerations: - This would be a good moment to merge the 2 repos, so that there is no history loss. - `hls-plugin-api` will need to be released to Hackage prior to merging haskell/ghcide#963
1 parent 99bdba9 commit 2afcaf5

File tree

31 files changed

+359
-332
lines changed

31 files changed

+359
-332
lines changed

exe/Plugins.hs

Lines changed: 4 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -3,12 +3,13 @@
33
module Plugins where
44

55
import Ide.Types (IdePlugins)
6-
import Ide.Plugin (pluginDescToIdePlugins)
6+
import Ide.PluginUtils (pluginDescToIdePlugins)
77

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

1314
-- haskell-language-server optional plugins
1415

@@ -73,7 +74,7 @@ import Ide.Plugin.Brittany as Brittany
7374
-- These can be freely added or removed to tailor the available
7475
-- features of the server.
7576

76-
idePlugins :: Bool -> IdePlugins
77+
idePlugins :: Bool -> IdePlugins IdeState
7778
idePlugins includeExamples = pluginDescToIdePlugins allPlugins
7879
where
7980
allPlugins = if includeExamples

ghcide/ghcide.cabal

Lines changed: 5 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -56,6 +56,8 @@ library
5656
haskell-lsp-types == 0.22.*,
5757
haskell-lsp == 0.22.*,
5858
hie-compat,
59+
hls-plugin-api,
60+
lens,
5961
mtl,
6062
network-uri,
6163
parallel,
@@ -127,7 +129,6 @@ library
127129
include
128130
exposed-modules:
129131
Development.IDE
130-
Development.IDE.Compat
131132
Development.IDE.Core.Debouncer
132133
Development.IDE.Core.FileStore
133134
Development.IDE.Core.IdeConfiguration
@@ -163,6 +164,9 @@ library
163164
Development.IDE.Plugin
164165
Development.IDE.Plugin.Completions
165166
Development.IDE.Plugin.CodeAction
167+
Development.IDE.Plugin.Formatter
168+
Development.IDE.Plugin.GhcIde
169+
Development.IDE.Plugin.HLS
166170
Development.IDE.Plugin.Test
167171

168172
-- Unfortunately, we cannot use loadSession with ghc-lib since hie-bios uses

ghcide/src/Development/IDE.hs

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -9,6 +9,7 @@ module Development.IDE
99
import Development.IDE.Core.RuleTypes as X
1010
import Development.IDE.Core.Rules as X
1111
(getAtPoint
12+
,getClientConfigAction
1213
,getDefinition
1314
,getParsedModule
1415
,getTypeDefinition

ghcide/src/Development/IDE/Compat.hs

Lines changed: 0 additions & 19 deletions
This file was deleted.

ghcide/src/Development/IDE/Core/IdeConfiguration.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -88,4 +88,4 @@ isWorkspaceFile file =
8888
workspaceFolders
8989

9090
getClientSettings :: Action (Maybe Value)
91-
getClientSettings = unhashed . clientSettings <$> getIdeConfiguration
91+
getClientSettings = unhashed . clientSettings <$> getIdeConfiguration

ghcide/src/Development/IDE/Core/Rules.hs

Lines changed: 12 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -27,11 +27,14 @@ module Development.IDE.Core.Rules(
2727
highlightAtPoint,
2828
getDependencies,
2929
getParsedModule,
30+
getClientConfigAction,
3031
) where
3132

3233
import Fingerprint
3334

35+
import Data.Aeson (fromJSON, Result(Success), FromJSON)
3436
import Data.Binary hiding (get, put)
37+
import Data.Default
3538
import Data.Tuple.Extra
3639
import Control.Monad.Extra
3740
import Control.Monad.Trans.Class
@@ -890,6 +893,15 @@ getClientSettingsRule = defineEarlyCutOffNoFile $ \GetClientSettings -> do
890893
settings <- clientSettings <$> getIdeConfiguration
891894
return (BS.pack . show . hash $ settings, settings)
892895

896+
-- | Returns the client configurarion stored in the IdeState.
897+
-- You can use this function to access it from shake Rules
898+
getClientConfigAction :: (Default a, FromJSON a) => Action a
899+
getClientConfigAction = do
900+
mbVal <- unhashed <$> useNoFile_ GetClientSettings
901+
case fromJSON <$> mbVal of
902+
Just (Success c) -> return c
903+
_ -> return def
904+
893905
-- | For now we always use bytecode
894906
getLinkableType :: NormalizedFilePath -> Action (Maybe LinkableType)
895907
getLinkableType f = do

ghcide/src/Development/IDE/Plugin.hs

Lines changed: 10 additions & 13 deletions
Original file line numberDiff line numberDiff line change
@@ -1,14 +1,17 @@
1-
2-
module Development.IDE.Plugin(Plugin(..), codeActionPlugin, codeActionPluginWithRules,makeLspCommandId,getPid) where
1+
module Development.IDE.Plugin
2+
( Plugin(..)
3+
, codeActionPlugin
4+
, codeActionPluginWithRules
5+
, makeLspCommandId
6+
) where
37

48
import Data.Default
59
import qualified Data.Text as T
610
import Development.Shake
711
import Development.IDE.LSP.Server
8-
9-
import Language.Haskell.LSP.Types
10-
import Development.IDE.Compat
1112
import Development.IDE.Core.Rules
13+
import Ide.PluginUtils
14+
import Language.Haskell.LSP.Types
1215
import qualified Language.Haskell.LSP.Core as LSP
1316
import Language.Haskell.LSP.Messages
1417

@@ -50,11 +53,5 @@ codeActionPluginWithRules rr f = Plugin rr $ PartialHandlers $ \WithMessage{..}
5053
-- on that.
5154
makeLspCommandId :: T.Text -> IO T.Text
5255
makeLspCommandId command = do
53-
pid <- getPid
54-
return $ pid <> ":ghcide:" <> command
55-
56-
-- | Get the operating system process id for the running server
57-
-- instance. This should be the same for the lifetime of the instance,
58-
-- and different from that of any other currently running instance.
59-
getPid :: IO T.Text
60-
getPid = T.pack . show <$> getProcessID
56+
pid <- getProcessID
57+
return $ T.pack (show pid) <> ":ghcide:" <> command

hls-plugin-api/src/Ide/Plugin/Formatter.hs renamed to ghcide/src/Development/IDE/Plugin/Formatter.hs

Lines changed: 5 additions & 40 deletions
Original file line numberDiff line numberDiff line change
@@ -4,20 +4,17 @@
44
{-# LANGUAGE TypeApplications #-}
55
{-# LANGUAGE ViewPatterns #-}
66

7-
module Ide.Plugin.Formatter
7+
module Development.IDE.Plugin.Formatter
88
(
99
formatting
1010
, rangeFormatting
11-
, noneProvider
12-
, responseError
13-
, extractRange
14-
, fullRange
1511
)
1612
where
1713

1814
import qualified Data.Map as Map
1915
import qualified Data.Text as T
2016
import Development.IDE
17+
import Ide.PluginUtils
2118
import Ide.Types
2219
import Ide.Plugin.Config
2320
import qualified Language.Haskell.LSP.Core as LSP
@@ -26,7 +23,7 @@ import Text.Regex.TDFA.Text()
2623

2724
-- ---------------------------------------------------------------------
2825

29-
formatting :: Map.Map PluginId (FormattingProvider IO)
26+
formatting :: Map.Map PluginId (FormattingProvider IdeState IO)
3027
-> LSP.LspFuncs Config -> IdeState -> DocumentFormattingParams
3128
-> IO (Either ResponseError (List TextEdit))
3229
formatting providers lf ideState
@@ -35,7 +32,7 @@ formatting providers lf ideState
3532

3633
-- ---------------------------------------------------------------------
3734

38-
rangeFormatting :: Map.Map PluginId (FormattingProvider IO)
35+
rangeFormatting :: Map.Map PluginId (FormattingProvider IdeState IO)
3936
-> LSP.LspFuncs Config -> IdeState -> DocumentRangeFormattingParams
4037
-> IO (Either ResponseError (List TextEdit))
4138
rangeFormatting providers lf ideState
@@ -44,7 +41,7 @@ rangeFormatting providers lf ideState
4441

4542
-- ---------------------------------------------------------------------
4643

47-
doFormatting :: LSP.LspFuncs Config -> Map.Map PluginId (FormattingProvider IO)
44+
doFormatting :: LSP.LspFuncs Config -> Map.Map PluginId (FormattingProvider IdeState IO)
4845
-> IdeState -> FormattingType -> Uri -> FormattingOptions
4946
-> IO (Either ResponseError (List TextEdit))
5047
doFormatting lf providers ideState ft uri params = do
@@ -76,35 +73,3 @@ doFormatting lf providers ideState ft uri params = do
7673
else ""
7774
]
7875

79-
-- ---------------------------------------------------------------------
80-
81-
noneProvider :: FormattingProvider IO
82-
noneProvider _ _ _ _ _ _ = return $ Right (List [])
83-
84-
-- ---------------------------------------------------------------------
85-
86-
responseError :: T.Text -> ResponseError
87-
responseError txt = ResponseError InvalidParams txt Nothing
88-
89-
-- ---------------------------------------------------------------------
90-
91-
extractRange :: Range -> T.Text -> T.Text
92-
extractRange (Range (Position sl _) (Position el _)) s = newS
93-
where focusLines = take (el-sl+1) $ drop sl $ T.lines s
94-
newS = T.unlines focusLines
95-
96-
-- | Gets the range that covers the entire text
97-
fullRange :: T.Text -> Range
98-
fullRange s = Range startPos endPos
99-
where startPos = Position 0 0
100-
endPos = Position lastLine 0
101-
{-
102-
In order to replace everything including newline characters,
103-
the end range should extend below the last line. From the specification:
104-
"If you want to specify a range that contains a line including
105-
the line ending character(s) then use an end position denoting
106-
the start of the next line"
107-
-}
108-
lastLine = length $ T.lines s
109-
110-
-- ---------------------------------------------------------------------

hls-plugin-api/src/Ide/Plugin/GhcIde.hs renamed to ghcide/src/Development/IDE/Plugin/GhcIde.hs

Lines changed: 8 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,6 @@
11
{-# LANGUAGE DuplicateRecordFields #-}
22
{-# LANGUAGE OverloadedStrings #-}
3-
module Ide.Plugin.GhcIde
3+
module Development.IDE.Plugin.GhcIde
44
(
55
descriptor
66
) where
@@ -11,14 +11,14 @@ import Development.IDE.Plugin.Completions
1111
import Development.IDE.Plugin.CodeAction
1212
import Development.IDE.LSP.HoverDefinition
1313
import Development.IDE.LSP.Outline
14-
import Ide.Plugin
14+
import Ide.PluginUtils
1515
import Ide.Types
1616
import Language.Haskell.LSP.Types
1717
import Text.Regex.TDFA.Text()
1818

1919
-- ---------------------------------------------------------------------
2020

21-
descriptor :: PluginId -> PluginDescriptor
21+
descriptor :: PluginId -> PluginDescriptor IdeState
2222
descriptor plId = (defaultPluginDescriptor plId)
2323
{ pluginCommands = [PluginCommand (CommandId "typesignature.add") "adds a signature" commandAddSignature]
2424
, pluginCodeActionProvider = Just codeAction'
@@ -30,30 +30,30 @@ descriptor plId = (defaultPluginDescriptor plId)
3030

3131
-- ---------------------------------------------------------------------
3232

33-
hover' :: HoverProvider
33+
hover' :: HoverProvider IdeState
3434
hover' ideState params = do
3535
logInfo (ideLogger ideState) "GhcIde.hover entered (ideLogger)" -- AZ
3636
hover ideState params
3737

3838
-- ---------------------------------------------------------------------
3939

40-
commandAddSignature :: CommandFunction WorkspaceEdit
40+
commandAddSignature :: CommandFunction IdeState WorkspaceEdit
4141
commandAddSignature lf ide params
4242
= commandHandler lf ide (ExecuteCommandParams "typesignature.add" (Just (List [toJSON params])) Nothing)
4343

4444
-- ---------------------------------------------------------------------
4545

46-
codeAction' :: CodeActionProvider
46+
codeAction' :: CodeActionProvider IdeState
4747
codeAction' lf ide _ doc range context = fmap List <$> codeAction lf ide doc range context
4848

4949
-- ---------------------------------------------------------------------
5050

51-
codeLens' :: CodeLensProvider
51+
codeLens' :: CodeLensProvider IdeState
5252
codeLens' lf ide _ params = codeLens lf ide params
5353

5454
-- ---------------------------------------------------------------------
5555

56-
symbolsProvider :: SymbolsProvider
56+
symbolsProvider :: SymbolsProvider IdeState
5757
symbolsProvider ls ide params = do
5858
ds <- moduleOutline ls ide params
5959
case ds of

0 commit comments

Comments
 (0)