Skip to content

Commit 9583e09

Browse files
committed
Deduplicate HLS plugins
Use a smart constructor to prevent duplicated plugins. We cannot use a set since order matters
1 parent c9ed045 commit 9583e09

File tree

1 file changed

+39
-3
lines changed

1 file changed

+39
-3
lines changed

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

Lines changed: 39 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -12,6 +12,7 @@
1212
{-# LANGUAGE MultiParamTypeClasses #-}
1313
{-# LANGUAGE NamedFieldPuns #-}
1414
{-# LANGUAGE OverloadedStrings #-}
15+
{-# LANGUAGE PatternSynonyms #-}
1516
{-# LANGUAGE PolyKinds #-}
1617
{-# LANGUAGE RecordWildCards #-}
1718
{-# LANGUAGE ScopedTypeVariables #-}
@@ -20,6 +21,30 @@
2021
{-# LANGUAGE ViewPatterns #-}
2122

2223
module Ide.Types
24+
( PluginDescriptor(..), defaultPluginDescriptor, defaultCabalPluginDescriptor
25+
, IdeCommand(..)
26+
, IdeMethod(..)
27+
, IdeNotification(..)
28+
, IdePlugins(IdePlugins, ipMap)
29+
, DynFlagsModifications(..)
30+
, ConfigDescriptor(..), defaultConfigDescriptor, configForPlugin, pluginEnabledConfig
31+
, CustomConfig(..), mkCustomConfig
32+
, FallbackCodeActionParams(..)
33+
, FormattingType(..), FormattingMethod, FormattingHandler, mkFormattingHandlers
34+
, HasTracing(..)
35+
, PluginCommand(..), CommandId(..), CommandFunction, mkLspCommand, mkLspCmdId
36+
, PluginId(..)
37+
, PluginHandler(..), mkPluginHandler
38+
, PluginHandlers(..)
39+
, PluginMethod(..)
40+
, PluginMethodHandler
41+
, PluginNotificationHandler(..), mkPluginNotificationHandler
42+
, PluginNotificationHandlers(..)
43+
, PluginRequestMethod(..)
44+
, getProcessID, getPid
45+
, installSigUsr1Handler
46+
, responseError
47+
)
2348
where
2449

2550
#ifdef mingw32_HOST_OS
@@ -36,6 +61,7 @@ import Data.Dependent.Map (DMap)
3661
import qualified Data.Dependent.Map as DMap
3762
import qualified Data.DList as DList
3863
import Data.GADT.Compare
64+
import Data.List.Extra (nubOrdOn)
3965
import Data.List.NonEmpty (NonEmpty (..), toList)
4066
import qualified Data.Map as Map
4167
import Data.Maybe
@@ -76,9 +102,19 @@ import Text.Regex.TDFA.Text ()
76102

77103
-- ---------------------------------------------------------------------
78104

79-
newtype IdePlugins ideState = IdePlugins
80-
{ ipMap :: [(PluginId, PluginDescriptor ideState)]}
81-
deriving newtype (Monoid, Semigroup)
105+
newtype IdePlugins ideState = IdePlugins_
106+
{ ipMap_ :: [(PluginId, PluginDescriptor ideState)]}
107+
deriving newtype Monoid
108+
109+
-- | Smart constructor that deduplicates plugins
110+
pattern IdePlugins :: [(PluginId, PluginDescriptor ideState)] -> IdePlugins ideState
111+
pattern IdePlugins{ipMap} <- IdePlugins_ ipMap
112+
where
113+
IdePlugins ipMap = IdePlugins_{ipMap_ = nubOrdOn fst ipMap}
114+
{-# COMPLETE IdePlugins #-}
115+
116+
instance Semigroup (IdePlugins s) where
117+
IdePlugins a <> IdePlugins b = IdePlugins(a <> b)
82118

83119
-- | Hooks for modifying the 'DynFlags' at different times of the compilation
84120
-- process. Plugins can install a 'DynFlagsModifications' via

0 commit comments

Comments
 (0)