Skip to content

Commit

Permalink
Invert the dependency between ghcide and hls-plugin-api
Browse files Browse the repository at this point in the history
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
  • Loading branch information
pepeiborra committed Dec 29, 2020
1 parent d4f5d43 commit ebf0332
Show file tree
Hide file tree
Showing 31 changed files with 361 additions and 332 deletions.
7 changes: 4 additions & 3 deletions exe/Plugins.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,12 +3,13 @@
module Plugins where

import Ide.Types (IdePlugins)
import Ide.Plugin (pluginDescToIdePlugins)
import Ide.PluginUtils (pluginDescToIdePlugins)

-- fixed plugins
import Ide.Plugin.Example as Example
import Ide.Plugin.Example2 as Example2
import Ide.Plugin.GhcIde as GhcIde
import Development.IDE (IdeState)
import Development.IDE.Plugin.HLS.GhcIde as GhcIde

-- haskell-language-server optional plugins

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

idePlugins :: Bool -> IdePlugins
idePlugins :: Bool -> IdePlugins IdeState
idePlugins includeExamples = pluginDescToIdePlugins allPlugins
where
allPlugins = if includeExamples
Expand Down
6 changes: 5 additions & 1 deletion ghcide/ghcide.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -56,6 +56,8 @@ library
haskell-lsp-types == 0.22.*,
haskell-lsp == 0.22.*,
hie-compat,
hls-plugin-api,
lens,
mtl,
network-uri,
parallel,
Expand Down Expand Up @@ -127,7 +129,6 @@ library
include
exposed-modules:
Development.IDE
Development.IDE.Compat
Development.IDE.Core.Debouncer
Development.IDE.Core.FileStore
Development.IDE.Core.IdeConfiguration
Expand Down Expand Up @@ -163,6 +164,8 @@ library
Development.IDE.Plugin
Development.IDE.Plugin.Completions
Development.IDE.Plugin.CodeAction
Development.IDE.Plugin.HLS
Development.IDE.Plugin.HLS.GhcIde
Development.IDE.Plugin.Test

-- Unfortunately, we cannot use loadSession with ghc-lib since hie-bios uses
Expand Down Expand Up @@ -190,6 +193,7 @@ library
Development.IDE.Plugin.CodeAction.RuleTypes
Development.IDE.Plugin.Completions.Logic
Development.IDE.Plugin.Completions.Types
Development.IDE.Plugin.HLS.Formatter
Development.IDE.Types.Action
ghc-options: -Wall -Wno-name-shadowing -Wincomplete-uni-patterns

Expand Down
1 change: 1 addition & 0 deletions ghcide/src/Development/IDE.hs
Original file line number Diff line number Diff line change
Expand Up @@ -9,6 +9,7 @@ module Development.IDE
import Development.IDE.Core.RuleTypes as X
import Development.IDE.Core.Rules as X
(getAtPoint
,getClientConfigAction
,getDefinition
,getParsedModule
,getTypeDefinition
Expand Down
19 changes: 0 additions & 19 deletions ghcide/src/Development/IDE/Compat.hs

This file was deleted.

2 changes: 1 addition & 1 deletion ghcide/src/Development/IDE/Core/IdeConfiguration.hs
Original file line number Diff line number Diff line change
Expand Up @@ -88,4 +88,4 @@ isWorkspaceFile file =
workspaceFolders

getClientSettings :: Action (Maybe Value)
getClientSettings = unhashed . clientSettings <$> getIdeConfiguration
getClientSettings = unhashed . clientSettings <$> getIdeConfiguration
12 changes: 12 additions & 0 deletions ghcide/src/Development/IDE/Core/Rules.hs
Original file line number Diff line number Diff line change
Expand Up @@ -27,11 +27,14 @@ module Development.IDE.Core.Rules(
highlightAtPoint,
getDependencies,
getParsedModule,
getClientConfigAction,
) where

import Fingerprint

import Data.Aeson (fromJSON, Result(Success), FromJSON)
import Data.Binary hiding (get, put)
import Data.Default
import Data.Tuple.Extra
import Control.Monad.Extra
import Control.Monad.Trans.Class
Expand Down Expand Up @@ -890,6 +893,15 @@ getClientSettingsRule = defineEarlyCutOffNoFile $ \GetClientSettings -> do
settings <- clientSettings <$> getIdeConfiguration
return (BS.pack . show . hash $ settings, settings)

-- | Returns the client configurarion stored in the IdeState.
-- You can use this function to access it from shake Rules
getClientConfigAction :: (Default a, FromJSON a) => Action a
getClientConfigAction = do
mbVal <- unhashed <$> useNoFile_ GetClientSettings
case fromJSON <$> mbVal of
Just (Success c) -> return c
_ -> return def

-- | For now we always use bytecode
getLinkableType :: NormalizedFilePath -> Action (Maybe LinkableType)
getLinkableType f = do
Expand Down
23 changes: 10 additions & 13 deletions ghcide/src/Development/IDE/Plugin.hs
Original file line number Diff line number Diff line change
@@ -1,14 +1,17 @@

module Development.IDE.Plugin(Plugin(..), codeActionPlugin, codeActionPluginWithRules,makeLspCommandId,getPid) where
module Development.IDE.Plugin
( Plugin(..)
, codeActionPlugin
, codeActionPluginWithRules
, makeLspCommandId
) where

import Data.Default
import qualified Data.Text as T
import Development.Shake
import Development.IDE.LSP.Server

import Language.Haskell.LSP.Types
import Development.IDE.Compat
import Development.IDE.Core.Rules
import Ide.PluginUtils
import Language.Haskell.LSP.Types
import qualified Language.Haskell.LSP.Core as LSP
import Language.Haskell.LSP.Messages

Expand Down Expand Up @@ -50,11 +53,5 @@ codeActionPluginWithRules rr f = Plugin rr $ PartialHandlers $ \WithMessage{..}
-- on that.
makeLspCommandId :: T.Text -> IO T.Text
makeLspCommandId command = do
pid <- getPid
return $ pid <> ":ghcide:" <> command

-- | Get the operating system process id for the running server
-- instance. This should be the same for the lifetime of the instance,
-- and different from that of any other currently running instance.
getPid :: IO T.Text
getPid = T.pack . show <$> getProcessID
pid <- getProcessID
return $ T.pack (show pid) <> ":ghcide:" <> command
Loading

0 comments on commit ebf0332

Please sign in to comment.