Skip to content
This repository has been archived by the owner on Jan 2, 2021. It is now read-only.

Invert the dependency with hls-plugin-api #963

Closed
wants to merge 2 commits into from
Closed
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
6 changes: 5 additions & 1 deletion ghcide.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -55,6 +55,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 @@ -126,7 +128,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 @@ -161,6 +162,9 @@ library
Development.IDE.Plugin
Development.IDE.Plugin.Completions
Development.IDE.Plugin.CodeAction
Development.IDE.Plugin.Formatter
Copy link
Collaborator

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Why do these end up in Ghcide? I guess they leave in a future diff?

Copy link
Collaborator Author

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Formatter contains machinery needed to convert an HLS FormattingProvider into a PartialHandler for ghcide

Development.IDE.Plugin.GhcIde
Development.IDE.Plugin.HLS
Development.IDE.Plugin.Test

-- Unfortunately, we cannot use loadSession with ghc-lib since hie-bios uses
Expand Down
1 change: 1 addition & 0 deletions 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 src/Development/IDE/Compat.hs

This file was deleted.

2 changes: 1 addition & 1 deletion 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 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 @@ -886,6 +889,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 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
4 changes: 2 additions & 2 deletions src/Development/IDE/Plugin/CodeAction.hs
Original file line number Diff line number Diff line change
Expand Up @@ -648,7 +648,7 @@ suggestExtendImport exportsMap contents Diagnostic{_range=_range,..}
| Just (binding, mod_srcspan) <-
matchRegExMultipleImports _message
, Just c <- contents
= mod_srcspan >>= (\(x, y) -> suggestions c binding x y)
= mod_srcspan >>= (\(x, y) -> suggestions c binding x y)
| otherwise = []
where
suggestions c binding mod srcspan
Expand All @@ -664,7 +664,7 @@ suggestExtendImport exportsMap contents Diagnostic{_range=_range,..}
renderImport IdentInfo {parent, rendered}
| Just p <- parent = p <> "(" <> rendered <> ")"
| otherwise = rendered
lookupExportMap binding mod
lookupExportMap binding mod
| Just match <- Map.lookup binding (getExportsMap exportsMap)
, [(ident, _)] <- filter (\(_,m) -> mod == m) (Set.toList match)
= Just ident
Expand Down
2 changes: 1 addition & 1 deletion src/Development/IDE/Plugin/Completions/Logic.hs
Original file line number Diff line number Diff line change
Expand Up @@ -321,7 +321,7 @@ cacheDataProducer packageState curMod rdrEnv limports deps = do
getComplsForOne (GRE n _ False prov) =
flip foldMapM (map is_decl prov) $ \spec -> do
let originalImportDecl = Map.lookup (is_dloc spec) importMap
compItem <- toCompItem curMod (is_mod spec) n originalImportDecl
compItem <- toCompItem curMod (is_mod spec) n (const Nothing originalImportDecl)
let unqual
| is_qual spec = []
| otherwise = compItem
Expand Down
75 changes: 75 additions & 0 deletions src/Development/IDE/Plugin/Formatter.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,75 @@
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE ViewPatterns #-}

module Development.IDE.Plugin.Formatter
(
formatting
, rangeFormatting
)
where

import qualified Data.Map as Map
import qualified Data.Text as T
import Development.IDE
import Ide.PluginUtils
import Ide.Types
import Ide.Plugin.Config
import qualified Language.Haskell.LSP.Core as LSP
import Language.Haskell.LSP.Types
import Text.Regex.TDFA.Text()

-- ---------------------------------------------------------------------

formatting :: Map.Map PluginId (FormattingProvider IdeState IO)
-> LSP.LspFuncs Config -> IdeState -> DocumentFormattingParams
-> IO (Either ResponseError (List TextEdit))
formatting providers lf ideState
(DocumentFormattingParams (TextDocumentIdentifier uri) params _mprogress)
= doFormatting lf providers ideState FormatText uri params

-- ---------------------------------------------------------------------

rangeFormatting :: Map.Map PluginId (FormattingProvider IdeState IO)
-> LSP.LspFuncs Config -> IdeState -> DocumentRangeFormattingParams
-> IO (Either ResponseError (List TextEdit))
rangeFormatting providers lf ideState
(DocumentRangeFormattingParams (TextDocumentIdentifier uri) range params _mprogress)
= doFormatting lf providers ideState (FormatRange range) uri params

-- ---------------------------------------------------------------------

doFormatting :: LSP.LspFuncs Config -> Map.Map PluginId (FormattingProvider IdeState IO)
-> IdeState -> FormattingType -> Uri -> FormattingOptions
-> IO (Either ResponseError (List TextEdit))
doFormatting lf providers ideState ft uri params = do
mc <- LSP.config lf
let mf = maybe "none" formattingProvider mc
case Map.lookup (PluginId mf) providers of
Just provider ->
case uriToFilePath uri of
Just (toNormalizedFilePath -> fp) -> do
(_, mb_contents) <- runAction "Formatter" ideState $ getFileContents fp
case mb_contents of
Just contents -> do
logDebug (ideLogger ideState) $ T.pack $
"Formatter.doFormatting: contents=" ++ show contents -- AZ
provider lf ideState ft contents fp params
Nothing -> return $ Left $ responseError $ T.pack $ "Formatter plugin: could not get file contents for " ++ show uri
Nothing -> return $ Left $ responseError $ T.pack $ "Formatter plugin: uriToFilePath failed for: " ++ show uri
Nothing -> return $ Left $ responseError $ mconcat
[ "Formatter plugin: no formatter found for:["
, mf
, "]"
, if mf == "brittany"
then T.unlines
[ "\nThe haskell-language-server must be compiled with the agpl flag to provide Brittany."
, "Stack users add 'agpl: true' in the flags section of the 'stack.yaml' file."
, "The 'haskell-language-server.cabal' file already has this flag enabled by default."
, "For more information see: https://github.com/haskell/haskell-language-server/issues/269"
]
else ""
]

65 changes: 65 additions & 0 deletions src/Development/IDE/Plugin/GhcIde.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,65 @@
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE OverloadedStrings #-}
module Development.IDE.Plugin.GhcIde
(
descriptor
) where

import Data.Aeson
import Development.IDE
import Development.IDE.Plugin.Completions
import Development.IDE.Plugin.CodeAction
import Development.IDE.LSP.HoverDefinition
import Development.IDE.LSP.Outline
import Ide.PluginUtils
import Ide.Types
import Language.Haskell.LSP.Types
import Text.Regex.TDFA.Text()

-- ---------------------------------------------------------------------

descriptor :: PluginId -> PluginDescriptor IdeState
descriptor plId = (defaultPluginDescriptor plId)
{ pluginCommands = [PluginCommand (CommandId "typesignature.add") "adds a signature" commandAddSignature]
, pluginCodeActionProvider = Just codeAction'
, pluginCodeLensProvider = Just codeLens'
, pluginHoverProvider = Just hover'
, pluginSymbolsProvider = Just symbolsProvider
, pluginCompletionProvider = Just getCompletionsLSP
}

-- ---------------------------------------------------------------------

hover' :: HoverProvider IdeState
hover' ideState params = do
logInfo (ideLogger ideState) "GhcIde.hover entered (ideLogger)" -- AZ
hover ideState params

-- ---------------------------------------------------------------------

commandAddSignature :: CommandFunction IdeState WorkspaceEdit
commandAddSignature lf ide params
= commandHandler lf ide (ExecuteCommandParams "typesignature.add" (Just (List [toJSON params])) Nothing)

-- ---------------------------------------------------------------------

codeAction' :: CodeActionProvider IdeState
codeAction' lf ide _ doc range context = fmap List <$> codeAction lf ide doc range context

-- ---------------------------------------------------------------------

codeLens' :: CodeLensProvider IdeState
codeLens' lf ide _ params = codeLens lf ide params

-- ---------------------------------------------------------------------

symbolsProvider :: SymbolsProvider IdeState
symbolsProvider ls ide params = do
ds <- moduleOutline ls ide params
case ds of
Right (DSDocumentSymbols (List ls)) -> return $ Right ls
Right (DSSymbolInformation (List _si)) ->
return $ Left $ responseError "GhcIde.symbolsProvider: DSSymbolInformation deprecated"
Left err -> return $ Left err

-- ---------------------------------------------------------------------
Loading