Skip to content

Commit 2a7561b

Browse files
committed
Add plugin priorities
1 parent 8b96f46 commit 2a7561b

File tree

5 files changed

+34
-15
lines changed

5 files changed

+34
-15
lines changed

exe/Plugins.hs

Lines changed: 0 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -211,12 +211,8 @@ idePlugins recorder includeExamples = pluginDescToIdePlugins allPlugins
211211
#if hls_gadt
212212
GADT.descriptor "gadt" :
213213
#endif
214-
-- The ghcide descriptors should come last so that the notification handlers
215-
-- (which restart the Shake build) run after everything else
216214
GhcIde.descriptors pluginRecorder
217215
#if explicitFixity
218-
-- Make this plugin has a lower priority than ghcide's plugin to ensure
219-
-- type info display first.
220216
++ [ExplicitFixity.descriptor pluginRecorder]
221217
#endif
222218
examplePlugins =

ghcide/ghcide.cabal

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -192,6 +192,7 @@ library
192192
Development.IDE.Monitoring.EKG
193193
Development.IDE.LSP.HoverDefinition
194194
Development.IDE.LSP.LanguageServer
195+
Development.IDE.LSP.Notifications
195196
Development.IDE.LSP.Outline
196197
Development.IDE.LSP.Server
197198
Development.IDE.Session
@@ -225,7 +226,6 @@ library
225226
Development.IDE.Core.FileExists
226227
Development.IDE.GHC.CPP
227228
Development.IDE.GHC.Warnings
228-
Development.IDE.LSP.Notifications
229229
Development.IDE.Plugin.CodeAction.PositionIndexed
230230
Development.IDE.Plugin.CodeAction.Args
231231
Development.IDE.Plugin.Completions.Logic

ghcide/src/Development/IDE/LSP/Notifications.hs

Lines changed: 10 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -10,6 +10,7 @@ module Development.IDE.LSP.Notifications
1010
( whenUriFile
1111
, descriptor
1212
, Log(..)
13+
, ghcideNotificationsPluginPriority
1314
) where
1415

1516
import Language.LSP.Types
@@ -38,6 +39,7 @@ import Development.IDE.Types.Location
3839
import Development.IDE.Types.Logger
3940
import Development.IDE.Types.Shake (toKey)
4041
import Ide.Types
42+
import Numeric.Natural
4143

4244
data Log
4345
= LogShake Shake.Log
@@ -138,5 +140,12 @@ descriptor recorder plId = (defaultPluginDescriptor plId) { pluginNotificationHa
138140
success <- registerFileWatches globs
139141
unless success $
140142
liftIO $ logDebug (ideLogger ide) "Warning: Client does not support watched files. Falling back to OS polling"
141-
]
143+
],
144+
145+
-- The ghcide descriptors should come last'ish so that the notification handlers
146+
-- (which restart the Shake build) run after everything else
147+
pluginPriority = ghcideNotificationsPluginPriority
142148
}
149+
150+
ghcideNotificationsPluginPriority :: Natural
151+
ghcideNotificationsPluginPriority = defaultPluginPriority - 900

hls-plugin-api/src/Ide/Types.hs

Lines changed: 19 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -22,6 +22,7 @@
2222

2323
module Ide.Types
2424
( PluginDescriptor(..), defaultPluginDescriptor, defaultCabalPluginDescriptor
25+
, defaultPluginPriority
2526
, IdeCommand(..)
2627
, IdeMethod(..)
2728
, IdeNotification(..)
@@ -61,10 +62,14 @@ import Data.Dependent.Map (DMap)
6162
import qualified Data.Dependent.Map as DMap
6263
import qualified Data.DList as DList
6364
import Data.GADT.Compare
64-
import Data.List.Extra (nubOrdOn)
65+
import Data.Hashable (Hashable)
66+
import Data.HashMap.Strict (HashMap)
67+
import qualified Data.HashMap.Strict as HashMap
68+
import Data.List.Extra (sortOn)
6569
import Data.List.NonEmpty (NonEmpty (..), toList)
6670
import qualified Data.Map as Map
6771
import Data.Maybe
72+
import Data.Ord
6873
import Data.Semigroup
6974
import Data.String
7075
import qualified Data.Text as T
@@ -94,6 +99,7 @@ import Language.LSP.Types.Lens as J (HasChildren (children),
9499
HasTitle (title),
95100
HasUri (..))
96101
import Language.LSP.VFS
102+
import Numeric.Natural
97103
import OpenTelemetry.Eventlog
98104
import Options.Applicative (ParserInfo)
99105
import System.FilePath
@@ -102,20 +108,16 @@ import Text.Regex.TDFA.Text ()
102108

103109
-- ---------------------------------------------------------------------
104110

105-
newtype IdePlugins ideState = IdePlugins_
106-
{ ipMap_ :: [(PluginId, PluginDescriptor ideState)]}
107-
deriving newtype Monoid
111+
newtype IdePlugins ideState = IdePlugins_ { ipMap_ :: HashMap PluginId (PluginDescriptor ideState)}
112+
deriving newtype (Semigroup, Monoid)
108113

109114
-- | Smart constructor that deduplicates plugins
110115
pattern IdePlugins :: [(PluginId, PluginDescriptor ideState)] -> IdePlugins ideState
111-
pattern IdePlugins{ipMap} <- IdePlugins_ ipMap
116+
pattern IdePlugins{ipMap} <- IdePlugins_ (sortOn (Down . pluginPriority . snd) . HashMap.toList -> ipMap)
112117
where
113-
IdePlugins ipMap = IdePlugins_{ipMap_ = nubOrdOn fst ipMap}
118+
IdePlugins ipMap = IdePlugins_{ipMap_ = HashMap.fromList ipMap}
114119
{-# COMPLETE IdePlugins #-}
115120

116-
instance Semigroup (IdePlugins s) where
117-
IdePlugins a <> IdePlugins b = IdePlugins(a <> b)
118-
119121
-- | Hooks for modifying the 'DynFlags' at different times of the compilation
120122
-- process. Plugins can install a 'DynFlagsModifications' via
121123
-- 'pluginModifyDynflags' in their 'PluginDescriptor'.
@@ -149,6 +151,8 @@ instance Show (IdeCommand st) where show _ = "<ide command>"
149151
data PluginDescriptor (ideState :: *) =
150152
PluginDescriptor { pluginId :: !PluginId
151153
-- ^ Unique identifier of the plugin.
154+
, pluginPriority :: Natural
155+
-- ^ Plugin handlers are called in priority order, higher priority first
152156
, pluginRules :: !(Rules ())
153157
, pluginCommands :: ![PluginCommand ideState]
154158
, pluginHandlers :: PluginHandlers ideState
@@ -631,6 +635,9 @@ mkPluginNotificationHandler m f
631635
where
632636
f' pid ide vfs = f ide vfs pid
633637

638+
defaultPluginPriority :: Natural
639+
defaultPluginPriority = 1000
640+
634641
-- | Set up a plugin descriptor, initialized with default values.
635642
-- This is plugin descriptor is prepared for @haskell@ files, such as
636643
--
@@ -644,6 +651,7 @@ defaultPluginDescriptor :: PluginId -> PluginDescriptor ideState
644651
defaultPluginDescriptor plId =
645652
PluginDescriptor
646653
plId
654+
defaultPluginPriority
647655
mempty
648656
mempty
649657
mempty
@@ -663,6 +671,7 @@ defaultCabalPluginDescriptor :: PluginId -> PluginDescriptor ideState
663671
defaultCabalPluginDescriptor plId =
664672
PluginDescriptor
665673
plId
674+
defaultPluginPriority
666675
mempty
667676
mempty
668677
mempty
@@ -694,6 +703,7 @@ type CommandFunction ideState a
694703

695704
newtype PluginId = PluginId T.Text
696705
deriving (Show, Read, Eq, Ord)
706+
deriving newtype Hashable
697707

698708
instance IsString PluginId where
699709
fromString = PluginId . T.pack

plugins/hls-explicit-fixity-plugin/src/Ide/Plugin/ExplicitFixity.hs

Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -28,6 +28,7 @@ import qualified Development.IDE.Core.Shake as Shake
2828
import Development.IDE.GHC.Compat
2929
import Development.IDE.GHC.Compat.Util (FastString)
3030
import qualified Development.IDE.GHC.Compat.Util as Util
31+
import Development.IDE.LSP.Notifications (ghcideNotificationsPluginPriority)
3132
import GHC.Generics (Generic)
3233
import Ide.PluginUtils (getNormalizedFilePath,
3334
handleMaybeM,
@@ -42,6 +43,9 @@ descriptor :: Recorder (WithPriority Log) -> PluginDescriptor IdeState
4243
descriptor recorder = (defaultPluginDescriptor pluginId)
4344
{ pluginRules = fixityRule recorder
4445
, pluginHandlers = mkPluginHandler STextDocumentHover hover
46+
-- Make this plugin has a lower priority than ghcide's plugin to ensure
47+
-- type info display first.
48+
, pluginPriority = ghcideNotificationsPluginPriority - 1
4549
}
4650

4751
hover :: PluginMethodHandler IdeState TextDocumentHover

0 commit comments

Comments
 (0)