Skip to content

Commit

Permalink
Give plugins descriptions, include versions of key dependencies (hask…
Browse files Browse the repository at this point in the history
…ell#3903)

* Plugins have descriptions

* Plugins based on external tools report the version they are built with

* Sort plugins
  • Loading branch information
michaelpj authored Dec 17, 2023
1 parent 7b4f54d commit 2b49d9d
Show file tree
Hide file tree
Showing 39 changed files with 105 additions and 62 deletions.
14 changes: 7 additions & 7 deletions exe/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -13,19 +13,19 @@ import Data.Function ((&))
import Data.Functor ((<&>))
import Data.Maybe (catMaybes)
import Data.Text (Text)
import Ide.Logger (Doc, Priority (Error, Info),
import qualified HlsPlugins as Plugins
import Ide.Arguments (Arguments (..),
GhcideArguments (..),
getArguments)
import Ide.Logger (Doc, Priority (Error, Info),
Recorder,
WithPriority (WithPriority, priority),
cfilter, cmapWithPrio,
defaultLayoutOptions,
layoutPretty, logWith,
makeDefaultStderrRecorder,
renderStrict, withFileRecorder)
import qualified Ide.Logger as Logger
import qualified HlsPlugins as Plugins
import Ide.Arguments (Arguments (..),
GhcideArguments (..),
getArguments)
import qualified Ide.Logger as Logger
import Ide.Main (defaultMain)
import qualified Ide.Main as IdeMain
import Ide.PluginUtils (pluginDescToIdePlugins)
Expand Down Expand Up @@ -70,7 +70,7 @@ main = do
])
-- This plugin just installs a handler for the `initialized` notification, which then
-- picks up the LSP environment and feeds it to our recorders
let lspRecorderPlugin = (defaultPluginDescriptor "LSPRecorderCallback")
let lspRecorderPlugin = (defaultPluginDescriptor "LSPRecorderCallback" "Internal plugin")
{ pluginNotificationHandlers = mkPluginNotificationHandler LSP.SMethod_Initialized $ \_ _ _ _ -> do
env <- LSP.getLspEnv
liftIO $ (cb1 <> cb2) env
Expand Down
2 changes: 1 addition & 1 deletion ghcide/exe/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -100,7 +100,7 @@ main = withTelemetryLogger $ \telemetryLogger -> do
(lspMessageRecorder, cb2) <- Logger.withBacklog Logger.lspClientMessageRecorder
-- This plugin just installs a handler for the `initialized` notification, which then
-- picks up the LSP environment and feeds it to our recorders
let lspRecorderPlugin = (defaultPluginDescriptor "LSPRecorderCallback")
let lspRecorderPlugin = (defaultPluginDescriptor "LSPRecorderCallback" "Internal plugin")
{ pluginNotificationHandlers = mkPluginNotificationHandler LSP.SMethod_Initialized $ \_ _ _ _ -> do
env <- LSP.getLspEnv
liftIO $ (cb1 <> cb2) env
Expand Down
4 changes: 3 additions & 1 deletion ghcide/src/Development/IDE/LSP/Notifications.hs
Original file line number Diff line number Diff line change
Expand Up @@ -54,7 +54,7 @@ whenUriFile :: Uri -> (NormalizedFilePath -> IO ()) -> IO ()
whenUriFile uri act = whenJust (LSP.uriToFilePath uri) $ act . toNormalizedFilePath'

descriptor :: Recorder (WithPriority Log) -> PluginId -> PluginDescriptor IdeState
descriptor recorder plId = (defaultPluginDescriptor plId) { pluginNotificationHandlers = mconcat
descriptor recorder plId = (defaultPluginDescriptor plId desc) { pluginNotificationHandlers = mconcat
[ mkPluginNotificationHandler LSP.SMethod_TextDocumentDidOpen $
\ide vfs _ (DidOpenTextDocumentParams TextDocumentItem{_uri,_version}) -> liftIO $ do
atomically $ updatePositionMapping ide (VersionedTextDocumentIdentifier _uri _version) []
Expand Down Expand Up @@ -142,6 +142,8 @@ descriptor recorder plId = (defaultPluginDescriptor plId) { pluginNotificationHa
-- (which restart the Shake build) run after everything else
pluginPriority = ghcideNotificationsPluginPriority
}
where
desc = "Handles basic notifications for ghcide"

ghcideNotificationsPluginPriority :: Natural
ghcideNotificationsPluginPriority = defaultPluginPriority - 900
4 changes: 3 additions & 1 deletion ghcide/src/Development/IDE/Plugin/Completions.hs
Original file line number Diff line number Diff line change
Expand Up @@ -71,13 +71,15 @@ ghcideCompletionsPluginPriority :: Natural
ghcideCompletionsPluginPriority = defaultPluginPriority

descriptor :: Recorder (WithPriority Log) -> PluginId -> PluginDescriptor IdeState
descriptor recorder plId = (defaultPluginDescriptor plId)
descriptor recorder plId = (defaultPluginDescriptor plId desc)
{ pluginRules = produceCompletions recorder
, pluginHandlers = mkPluginHandler SMethod_TextDocumentCompletion getCompletionsLSP
<> mkResolveHandler SMethod_CompletionItemResolve resolveCompletion
, pluginConfigDescriptor = defaultConfigDescriptor {configCustomConfig = mkCustomConfig properties}
, pluginPriority = ghcideCompletionsPluginPriority
}
where
desc = "Provides Haskell completions"


produceCompletions :: Recorder (WithPriority Log) -> Rules ()
Expand Down
4 changes: 3 additions & 1 deletion ghcide/src/Development/IDE/Plugin/HLS/GhcIde.hs
Original file line number Diff line number Diff line change
Expand Up @@ -42,7 +42,7 @@ descriptors recorder =
-- ---------------------------------------------------------------------

descriptor :: PluginId -> PluginDescriptor IdeState
descriptor plId = (defaultPluginDescriptor plId)
descriptor plId = (defaultPluginDescriptor plId desc)
{ pluginHandlers = mkPluginHandler SMethod_TextDocumentHover hover'
<> mkPluginHandler SMethod_TextDocumentDocumentSymbol moduleOutline
<> mkPluginHandler SMethod_TextDocumentDefinition (\ide _ DefinitionParams{..} ->
Expand All @@ -56,6 +56,8 @@ descriptor plId = (defaultPluginDescriptor plId)

pluginConfigDescriptor = defaultConfigDescriptor
}
where
desc = "Provides core IDE features for Haskell"

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

Expand Down
4 changes: 2 additions & 2 deletions ghcide/src/Development/IDE/Plugin/Test.hs
Original file line number Diff line number Diff line change
Expand Up @@ -77,7 +77,7 @@ newtype WaitForIdeRuleResult = WaitForIdeRuleResult { ideResultSuccess::Bool}
deriving newtype (FromJSON, ToJSON)

plugin :: PluginDescriptor IdeState
plugin = (defaultPluginDescriptor "test") {
plugin = (defaultPluginDescriptor "test" "") {
pluginHandlers = mkPluginHandler (SMethod_CustomMethod (Proxy @"test")) $ \st _ ->
testRequestHandler' st
}
Expand Down Expand Up @@ -166,7 +166,7 @@ blockCommandId :: Text
blockCommandId = "ghcide.command.block"

blockCommandDescriptor :: PluginId -> PluginDescriptor state
blockCommandDescriptor plId = (defaultPluginDescriptor plId) {
blockCommandDescriptor plId = (defaultPluginDescriptor plId "") {
pluginCommands = [PluginCommand (CommandId blockCommandId) "blocks forever" blockCommandHandler]
}

Expand Down
4 changes: 3 additions & 1 deletion ghcide/src/Development/IDE/Plugin/TypeLenses.hs
Original file line number Diff line number Diff line change
Expand Up @@ -94,13 +94,15 @@ typeLensCommandId = "typesignature.add"

descriptor :: Recorder (WithPriority Log) -> PluginId -> PluginDescriptor IdeState
descriptor recorder plId =
(defaultPluginDescriptor plId)
(defaultPluginDescriptor plId desc)
{ pluginHandlers = mkPluginHandler SMethod_TextDocumentCodeLens codeLensProvider
<> mkResolveHandler SMethod_CodeLensResolve codeLensResolveProvider
, pluginCommands = [PluginCommand (CommandId typeLensCommandId) "adds a signature" commandHandler]
, pluginRules = rules recorder
, pluginConfigDescriptor = defaultConfigDescriptor {configCustomConfig = mkCustomConfig properties}
}
where
desc = "Provides code lenses type signatures"

properties :: Properties '[ 'PropertyKey "mode" (TEnum Mode)]
properties = emptyProperties
Expand Down
8 changes: 4 additions & 4 deletions ghcide/test/exe/ExceptionTests.hs
Original file line number Diff line number Diff line change
Expand Up @@ -41,7 +41,7 @@ tests recorder logger = do
[ testCase "PluginHandlers" $ do
let pluginId = "plugin-handler-exception"
plugins = pluginDescToIdePlugins $
[ (defaultPluginDescriptor pluginId)
[ (defaultPluginDescriptor pluginId "")
{ pluginHandlers = mconcat
[ mkPluginHandler SMethod_TextDocumentCodeLens $ \_ _ _-> do
_ <- liftIO $ throwIO DivideByZero
Expand All @@ -62,7 +62,7 @@ tests recorder logger = do
let pluginId = "command-exception"
commandId = CommandId "exception"
plugins = pluginDescToIdePlugins $
[ (defaultPluginDescriptor pluginId)
[ (defaultPluginDescriptor pluginId "")
{ pluginCommands =
[ PluginCommand commandId "Causes an exception" $ \_ (_::Int) -> do
_ <- liftIO $ throwIO DivideByZero
Expand All @@ -84,7 +84,7 @@ tests recorder logger = do
, testCase "Notification Handlers" $ do
let pluginId = "notification-exception"
plugins = pluginDescToIdePlugins $
[ (defaultPluginDescriptor pluginId)
[ (defaultPluginDescriptor pluginId "")
{ pluginNotificationHandlers = mconcat
[ mkPluginNotificationHandler SMethod_TextDocumentDidOpen $ \_ _ _ _ ->
liftIO $ throwIO DivideByZero
Expand Down Expand Up @@ -137,7 +137,7 @@ pluginOrderTestCase recorder logger msg err1 err2 =
testCase msg $ do
let pluginId = "error-order-test"
plugins = pluginDescToIdePlugins $
[ (defaultPluginDescriptor pluginId)
[ (defaultPluginDescriptor pluginId "")
{ pluginHandlers = mconcat
[ mkPluginHandler SMethod_TextDocumentCodeLens $ \_ _ _-> do
throwError $ err1 "error test"
Expand Down
2 changes: 1 addition & 1 deletion ghcide/test/exe/UnitTests.hs
Original file line number Diff line number Diff line change
Expand Up @@ -80,7 +80,7 @@ tests recorder logger = do
}
| i <- [1..20]
] ++ Ghcide.descriptors (cmapWithPrio LogGhcIde recorder)
priorityPluginDescriptor i = (defaultPluginDescriptor $ fromString $ show i){pluginPriority = i}
priorityPluginDescriptor i = (defaultPluginDescriptor (fromString $ show i) ""){pluginPriority = i}

testIde recorder (IDE.testing (cmapWithPrio LogIDEMain recorder) logger plugins) $ do
_ <- createDoc "A.hs" "haskell" "module A where"
Expand Down
20 changes: 16 additions & 4 deletions hls-plugin-api/src/Ide/Types.hs
Original file line number Diff line number Diff line change
Expand Up @@ -25,6 +25,7 @@
module Ide.Types
( PluginDescriptor(..), defaultPluginDescriptor, defaultCabalPluginDescriptor
, defaultPluginPriority
, describePlugin
, IdeCommand(..)
, IdeMethod(..)
, IdeNotification(..)
Expand Down Expand Up @@ -104,6 +105,7 @@ import Language.LSP.VFS
import Numeric.Natural
import OpenTelemetry.Eventlog
import Options.Applicative (ParserInfo)
import Prettyprinter as PP
import System.FilePath
import System.IO.Unsafe
import Text.Regex.TDFA.Text ()
Expand Down Expand Up @@ -266,6 +268,7 @@ instance ToJSON PluginConfig where

data PluginDescriptor (ideState :: Type) =
PluginDescriptor { pluginId :: !PluginId
, pluginDescription :: !T.Text
-- ^ Unique identifier of the plugin.
, pluginPriority :: Natural
-- ^ Plugin handlers are called in priority order, higher priority first
Expand All @@ -283,6 +286,13 @@ data PluginDescriptor (ideState :: Type) =
-- The file extension must have a leading '.'.
}

describePlugin :: PluginDescriptor c -> Doc ann
describePlugin p =
let
PluginId pid = pluginId p
pdesc = pluginDescription p
in pretty pid <> ":" <> nest 4 (PP.line <> pretty pdesc)

-- | Check whether the given plugin descriptor is responsible for the file with the given path.
-- Compares the file extension of the file at the given path with the file extension
-- the plugin is responsible for.
Expand Down Expand Up @@ -894,10 +904,11 @@ defaultPluginPriority = 1000
--
-- and handlers will be enabled for files with the appropriate file
-- extensions.
defaultPluginDescriptor :: PluginId -> PluginDescriptor ideState
defaultPluginDescriptor plId =
defaultPluginDescriptor :: PluginId -> T.Text -> PluginDescriptor ideState
defaultPluginDescriptor plId desc =
PluginDescriptor
plId
desc
defaultPluginPriority
mempty
mempty
Expand All @@ -914,10 +925,11 @@ defaultPluginDescriptor plId =
--
-- Handles files with the following extensions:
-- * @.cabal@
defaultCabalPluginDescriptor :: PluginId -> PluginDescriptor ideState
defaultCabalPluginDescriptor plId =
defaultCabalPluginDescriptor :: PluginId -> T.Text -> PluginDescriptor ideState
defaultCabalPluginDescriptor plId desc =
PluginDescriptor
plId
desc
defaultPluginPriority
mempty
mempty
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -44,7 +44,7 @@ instance Pretty Log where
LogShake log -> pretty log

descriptor :: Recorder (WithPriority Log) -> PluginId -> PluginDescriptor IdeState
descriptor recorder pId = (defaultPluginDescriptor pId)
descriptor recorder pId = (defaultPluginDescriptor pId "Provides code actions to convert numeric literals to different formats")
{ pluginHandlers = mkPluginHandler SMethod_TextDocumentCodeAction codeActionHandler
, pluginRules = collectLiteralsRule recorder
}
Expand Down
2 changes: 1 addition & 1 deletion plugins/hls-cabal-fmt-plugin/src/Ide/Plugin/CabalFmt.hs
Original file line number Diff line number Diff line change
Expand Up @@ -39,7 +39,7 @@ instance Pretty Log where

descriptor :: Recorder (WithPriority Log) -> PluginId -> PluginDescriptor IdeState
descriptor recorder plId =
(defaultCabalPluginDescriptor plId)
(defaultCabalPluginDescriptor plId "Provides formatting of cabal files with cabal-fmt")
{ pluginHandlers = mkFormattingHandlers (provider recorder)
}

Expand Down
2 changes: 1 addition & 1 deletion plugins/hls-cabal-plugin/src/Ide/Plugin/Cabal.hs
Original file line number Diff line number Diff line change
Expand Up @@ -80,7 +80,7 @@ instance Pretty Log where

descriptor :: Recorder (WithPriority Log) -> PluginId -> PluginDescriptor IdeState
descriptor recorder plId =
(defaultCabalPluginDescriptor plId)
(defaultCabalPluginDescriptor plId "Provides a variety of IDE features in cabal files")
{ pluginRules = cabalRules recorder
, pluginHandlers =
mconcat
Expand Down
Original file line number Diff line number Diff line change
@@ -1,3 +1,4 @@
{-# LANGUAGE OverloadedStrings #-}
module Ide.Plugin.CallHierarchy (descriptor) where

import Development.IDE
Expand All @@ -6,7 +7,7 @@ import Ide.Types
import Language.LSP.Protocol.Message

descriptor :: PluginId -> PluginDescriptor IdeState
descriptor plId = (defaultPluginDescriptor plId)
descriptor plId = (defaultPluginDescriptor plId "Provides call-hierarchy support in Haskell")
{ Ide.Types.pluginHandlers =
mkPluginHandler SMethod_TextDocumentPrepareCallHierarchy X.prepareCallHierarchy
<> mkPluginHandler SMethod_CallHierarchyIncomingCalls X.incomingCalls
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -33,7 +33,8 @@ import Language.LSP.Protocol.Types
import Text.Regex.TDFA ((=~))

descriptor :: PluginId -> PluginDescriptor IdeState
descriptor plId = (defaultPluginDescriptor plId) { pluginHandlers = mkPluginHandler SMethod_TextDocumentCodeAction (codeActionHandler plId) }
descriptor plId = (defaultPluginDescriptor plId "Provides a code action to change the type signature of a binding if it is wrong")
{ pluginHandlers = mkPluginHandler SMethod_TextDocumentCodeAction (codeActionHandler plId) }

codeActionHandler :: PluginId -> PluginMethodHandler IdeState 'Method_TextDocumentCodeAction
codeActionHandler plId ideState _ CodeActionParams {_textDocument = TextDocumentIdentifier uri, _context = CodeActionContext diags _ _} = do
Expand Down
2 changes: 1 addition & 1 deletion plugins/hls-class-plugin/src/Ide/Plugin/Class.hs
Original file line number Diff line number Diff line change
Expand Up @@ -8,7 +8,7 @@ import Ide.Plugin.Class.Types
import Ide.Types
import Language.LSP.Protocol.Message
descriptor :: Recorder (WithPriority Log) -> PluginId -> PluginDescriptor IdeState
descriptor recorder plId = (defaultPluginDescriptor plId)
descriptor recorder plId = (defaultPluginDescriptor plId "Provides code actions and lenses for working with typeclasses")
{ pluginCommands = commands plId
, pluginRules = getInstanceBindTypeSigsRule recorder >> getInstanceBindLensRule recorder
, pluginHandlers = mkPluginHandler SMethod_TextDocumentCodeAction (codeAction recorder)
Expand Down
2 changes: 1 addition & 1 deletion plugins/hls-code-range-plugin/src/Ide/Plugin/CodeRange.hs
Original file line number Diff line number Diff line change
Expand Up @@ -57,7 +57,7 @@ import Language.LSP.Protocol.Types (FoldingRange (..),
import Prelude hiding (log, span)

descriptor :: Recorder (WithPriority Log) -> PluginId -> PluginDescriptor IdeState
descriptor recorder plId = (defaultPluginDescriptor plId)
descriptor recorder plId = (defaultPluginDescriptor plId "Provides selection and folding ranges for Haskell")
{ pluginHandlers = mkPluginHandler SMethod_TextDocumentSelectionRange (selectionRangeHandler recorder)
<> mkPluginHandler SMethod_TextDocumentFoldingRange (foldingRangeHandler recorder)
, pluginRules = codeRangeRule (cmapWithPrio LogRules recorder)
Expand Down
3 changes: 2 additions & 1 deletion plugins/hls-eval-plugin/src/Ide/Plugin/Eval.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,5 @@
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# OPTIONS_GHC -Wwarn #-}
{-# LANGUAGE LambdaCase #-}
Expand Down Expand Up @@ -34,7 +35,7 @@ instance Pretty Log where
-- |Plugin descriptor
descriptor :: Recorder (WithPriority Log) -> PluginId -> PluginDescriptor IdeState
descriptor recorder plId =
(defaultPluginDescriptor plId)
(defaultPluginDescriptor plId "Provies a code lens to evaluate expressions in doctest comments")
{ pluginHandlers = mkPluginHandler SMethod_TextDocumentCodeLens CL.codeLens
, pluginCommands = [CL.evalCommand plId]
, pluginRules = rules (cmapWithPrio LogEvalRules recorder)
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -34,7 +34,7 @@ import Language.LSP.Protocol.Message
import Language.LSP.Protocol.Types

descriptor :: Recorder (WithPriority Log) -> PluginId -> PluginDescriptor IdeState
descriptor recorder pluginId = (defaultPluginDescriptor pluginId)
descriptor recorder pluginId = (defaultPluginDescriptor pluginId "Provides fixity information in hovers")
{ pluginRules = fixityRule recorder
, pluginHandlers = mkPluginHandler SMethod_TextDocumentHover hover
-- Make this plugin has a lower priority than ghcide's plugin to ensure
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -91,7 +91,7 @@ descriptorForModules
descriptorForModules recorder modFilter plId =
let resolveRecorder = cmapWithPrio LogResolve recorder
codeActionHandlers = mkCodeActionHandlerWithResolve resolveRecorder (codeActionProvider recorder) (codeActionResolveProvider recorder)
in (defaultPluginDescriptor plId)
in (defaultPluginDescriptor plId "Provides a code action to make imports explicit")
{
-- This plugin provides a command handler
pluginCommands = [PluginCommand importCommandId "Explicit import command" (runImportCommand recorder)],
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -106,7 +106,7 @@ descriptor :: Recorder (WithPriority Log) -> PluginId -> PluginDescriptor IdeSta
descriptor recorder plId =
let resolveRecorder = cmapWithPrio LogResolve recorder
(carCommands, caHandlers) = mkCodeActionWithResolveAndCommand resolveRecorder plId codeActionProvider codeActionResolveProvider
in (defaultPluginDescriptor plId)
in (defaultPluginDescriptor plId "Provides a code action to make record wildcards explicit")
{ pluginHandlers = caHandlers
, pluginCommands = carCommands
, pluginRules = collectRecordsRule recorder *> collectNamesRule
Expand Down
5 changes: 4 additions & 1 deletion plugins/hls-floskell-plugin/src/Ide/Plugin/Floskell.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,4 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE OverloadedStrings #-}

module Ide.Plugin.Floskell
Expand All @@ -20,9 +21,11 @@ import Language.LSP.Protocol.Types
-- ---------------------------------------------------------------------

descriptor :: PluginId -> PluginDescriptor IdeState
descriptor plId = (defaultPluginDescriptor plId)
descriptor plId = (defaultPluginDescriptor plId desc)
{ pluginHandlers = mkFormattingHandlers provider
}
where
desc = "Provides formatting of Haskell files via floskell. Built with floskell-" <> VERSION_floskell

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

Expand Down
4 changes: 3 additions & 1 deletion plugins/hls-fourmolu-plugin/src/Ide/Plugin/Fourmolu.hs
Original file line number Diff line number Diff line change
Expand Up @@ -49,10 +49,12 @@ import Text.Read (readMaybe)

descriptor :: Recorder (WithPriority LogEvent) -> PluginId -> PluginDescriptor IdeState
descriptor recorder plId =
(defaultPluginDescriptor plId)
(defaultPluginDescriptor plId desc)
{ pluginHandlers = mkFormattingHandlers $ provider recorder plId
, pluginConfigDescriptor = defaultConfigDescriptor{configCustomConfig = mkCustomConfig properties}
}
where
desc = "Provides formatting of Haskell files via fourmolu. Built with fourmolu-" <> VERSION_fourmolu

properties :: Properties '[ 'PropertyKey "external" 'TBoolean]
properties =
Expand Down
Loading

0 comments on commit 2b49d9d

Please sign in to comment.