Skip to content

Commit f8d6634

Browse files
author
Santiago Weight
committed
wingman: support 9.2.4
1 parent 1435ef8 commit f8d6634

File tree

30 files changed

+462
-237
lines changed

30 files changed

+462
-237
lines changed

ghcide/src/Development/IDE/Core/Rules.hs

+2-2
Original file line numberDiff line numberDiff line change
@@ -143,7 +143,7 @@ import Ide.Plugin.Properties (HasProperty,
143143
ToHsType,
144144
useProperty)
145145
import Ide.PluginUtils (configForPlugin)
146-
import Ide.Types (DynFlagsModifications (dynFlagsModifyGlobal, dynFlagsModifyParser),
146+
import Ide.Types (GhcOptsModifications (dynFlagsModifyGlobal, dynFlagsModifyParser),
147147
PluginId)
148148
import Control.Concurrent.STM.Stats (atomically)
149149
import Language.LSP.Server (LspT)
@@ -338,7 +338,7 @@ getParsedModuleWithCommentsRule recorder =
338338

339339
liftIO $ fmap (fmap reset_ms) $ snd <$> getParsedModuleDefinition (hscEnv sess) opt file ms
340340

341-
getModifyDynFlags :: (DynFlagsModifications -> a) -> Action a
341+
getModifyDynFlags :: (GhcOptsModifications -> a) -> Action a
342342
getModifyDynFlags f = do
343343
opts <- getIdeOptions
344344
cfg <- getClientConfigAction def

ghcide/src/Development/IDE/Plugin.hs

+2-2
Original file line numberDiff line numberDiff line change
@@ -4,13 +4,13 @@ import Data.Default
44
import Development.IDE.Graph
55

66
import Development.IDE.LSP.Server
7-
import Ide.Types (DynFlagsModifications)
7+
import Ide.Types (GhcOptsModifications)
88
import qualified Language.LSP.Server as LSP
99

1010
data Plugin c = Plugin
1111
{pluginRules :: Rules ()
1212
,pluginHandlers :: LSP.Handlers (ServerM c)
13-
,pluginModifyDynflags :: c -> DynFlagsModifications
13+
,pluginModifyDynflags :: c -> GhcOptsModifications
1414
}
1515

1616
instance Default (Plugin c) where

ghcide/src/Development/IDE/Plugin/HLS.hs

+1-1
Original file line numberDiff line numberDiff line change
@@ -125,7 +125,7 @@ rulesPlugins rs = mempty { P.pluginRules = rules }
125125
where
126126
rules = foldMap snd rs
127127

128-
dynFlagsPlugins :: [(PluginId, DynFlagsModifications)] -> Plugin Config
128+
dynFlagsPlugins :: [(PluginId, GhcOptsModifications)] -> Plugin Config
129129
dynFlagsPlugins rs = mempty
130130
{ P.pluginModifyDynflags =
131131
flip foldMap rs $ \(plId, dflag_mods) cfg ->

ghcide/src/Development/IDE/Types/Options.hs

+2-2
Original file line numberDiff line numberDiff line change
@@ -26,7 +26,7 @@ import Development.IDE.GHC.Compat as GHC
2626
import Development.IDE.Graph
2727
import Development.IDE.Types.Diagnostics
2828
import Ide.Plugin.Config
29-
import Ide.Types (DynFlagsModifications)
29+
import Ide.Types (GhcOptsModifications)
3030
import qualified Language.LSP.Types.Capabilities as LSP
3131

3232
data IdeOptions = IdeOptions
@@ -71,7 +71,7 @@ data IdeOptions = IdeOptions
7171
-- Otherwise, return the result of parsing without Opt_Haddock, so
7272
-- that the parsed module contains the result of Opt_KeepRawTokenStream,
7373
-- which might be necessary for hlint.
74-
, optModifyDynFlags :: Config -> DynFlagsModifications
74+
, optModifyDynFlags :: Config -> GhcOptsModifications
7575
-- ^ Will be called right after setting up a new cradle,
7676
-- allowing to customize the Ghc options used
7777
, optShakeOptions :: ShakeOptions

ghcide/src/Generics/SYB/GHC.hs

+27-1
Original file line numberDiff line numberDiff line change
@@ -1,13 +1,17 @@
11
{-# LANGUAGE DerivingVia #-}
22
{-# LANGUAGE RankNTypes #-}
3+
{-# LANGUAGE CPP #-}
34

45
-- | Custom SYB traversals explicitly designed for operating over the GHC AST.
56
module Generics.SYB.GHC
67
( genericIsSubspan,
78
mkBindListT,
89
everywhereM',
910
smallestM,
10-
largestM
11+
largestM,
12+
#if MIN_VERSION_ghc(9,2,1)
13+
genericIsSubspanL
14+
#endif
1115
) where
1216

1317
import Control.Monad
@@ -16,6 +20,10 @@ import Data.Monoid (Any (Any))
1620
import Development.IDE.GHC.Compat
1721
import Development.IDE.Graph.Classes
1822
import Generics.SYB
23+
#if MIN_VERSION_ghc(9,2,1)
24+
import GHC (LocatedL)
25+
import GHC.Hs (SrcSpanAnn' (..))
26+
#endif
1927

2028

2129
-- | A generic query intended to be used for calling 'smallestM' and
@@ -33,6 +41,24 @@ genericIsSubspan ::
3341
genericIsSubspan _ dst = mkQ Nothing $ \case
3442
(L span ast :: Located ast) -> Just (dst `isSubspanOf` span, ast)
3543

44+
#if MIN_VERSION_ghc(9,2,1)
45+
-- | A generic query intended to be used for calling 'smallestM' and
46+
-- 'largestM'. If the current node is a 'Located', returns whether or not the
47+
-- given 'SrcSpan' is a subspan. For all other nodes, returns 'Nothing', which
48+
-- indicates uncertainty. The search strategy in 'smallestM' et al. will
49+
-- continue searching uncertain nodes.
50+
genericIsSubspanL ::
51+
forall ast.
52+
Typeable ast =>
53+
-- | The type of nodes we'd like to consider.
54+
Proxy (LocatedL ast) ->
55+
SrcSpan ->
56+
GenericQ (Maybe (Bool, ast))
57+
genericIsSubspanL _ dst = mkQ Nothing $ \case
58+
(L (SrcSpanAnn _ span) ast :: LocatedL ast) -> Just (dst `isSubspanOf` span, ast)
59+
#endif
60+
61+
3662

3763
-- | Lift a function that replaces a value with several values into a generic
3864
-- function. The result doesn't perform any searching, so should be driven via

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

+37-20
Original file line numberDiff line numberDiff line change
@@ -26,8 +26,8 @@ module Ide.Types
2626
, IdeCommand(..)
2727
, IdeMethod(..)
2828
, IdeNotification(..)
29+
, GhcOptsModifications(..)
2930
, IdePlugins(IdePlugins, ipMap)
30-
, DynFlagsModifications(..)
3131
, ConfigDescriptor(..), defaultConfigDescriptor, configForPlugin, pluginEnabledConfig
3232
, CustomConfig(..), mkCustomConfig
3333
, FallbackCodeActionParams(..)
@@ -109,6 +109,11 @@ import System.FilePath
109109
import System.IO.Unsafe
110110
import Text.Regex.TDFA.Text ()
111111

112+
#if MIN_VERSION_ghc(9,2,0)
113+
import GHC.Plugins (StaticPlugin)
114+
#endif
115+
116+
112117
-- ---------------------------------------------------------------------
113118

114119
data IdePlugins ideState = IdePlugins_
@@ -137,28 +142,40 @@ lookupPluginId ls cmd = pluginId <$> find go ls
137142
where
138143
go desc = cmd `elem` map commandId (pluginCommands desc)
139144

140-
-- | Hooks for modifying the 'DynFlags' at different times of the compilation
141-
-- process. Plugins can install a 'DynFlagsModifications' via
142-
-- 'pluginModifyDynflags' in their 'PluginDescriptor'.
143-
data DynFlagsModifications =
144-
DynFlagsModifications
145-
{ -- | Invoked immediately at the package level. Changes to the 'DynFlags'
146-
-- made in 'dynFlagsModifyGlobal' are guaranteed to be seen everywhere in
147-
-- the compilation pipeline.
148-
dynFlagsModifyGlobal :: DynFlags -> DynFlags
149-
-- | Invoked just before the parsing step, and reset immediately
150-
-- afterwards. 'dynFlagsModifyParser' allows plugins to enable language
151-
-- extensions only during parsing. for example, to let them enable
152-
-- certain pieces of syntax.
145+
{- | Hooks for modifying the 'DynFlags' at different times of the compilation
146+
process. Plugins can install a 'GhcOptsModifications' via
147+
'pluginModifyDynflags' in their 'PluginDescriptor'.
148+
-}
149+
data GhcOptsModifications = GhcOptsModifications
150+
{ dynFlagsModifyGlobal :: DynFlags -> DynFlags
151+
-- ^ Invoked immediately at the package level. Changes to the 'DynFlags'
152+
-- made in 'dynFlagsModifyGlobal' are guaranteed to be seen everywhere in
153+
-- the compilation pipeline.
153154
, dynFlagsModifyParser :: DynFlags -> DynFlags
155+
-- ^ Invoked just before the parsing step, and reset immediately
156+
-- afterwards. 'dynFlagsModifyParser' allows plugins to enable language
157+
-- extensions only during parsing. for example, to let them enable
158+
-- certain pieces of syntax.
159+
#if MIN_VERSION_ghc(9,2,0)
160+
, staticPlugins :: [StaticPlugin]
161+
#endif
154162
}
155163

156-
instance Semigroup DynFlagsModifications where
157-
DynFlagsModifications g1 p1 <> DynFlagsModifications g2 p2 =
158-
DynFlagsModifications (g2 . g1) (p2 . p1)
164+
#if MIN_VERSION_ghc(9,2,0)
165+
instance Semigroup GhcOptsModifications where
166+
GhcOptsModifications g1 p1 plugins1 <> GhcOptsModifications g2 p2 plugins2 =
167+
GhcOptsModifications (g2 . g1) (p2 . p1) (plugins1 <> plugins2)
159168

160-
instance Monoid DynFlagsModifications where
161-
mempty = DynFlagsModifications id id
169+
instance Monoid GhcOptsModifications where
170+
mempty = GhcOptsModifications id id []
171+
#else
172+
instance Semigroup GhcOptsModifications where
173+
GhcOptsModifications g1 p1 <> GhcOptsModifications g2 p2 =
174+
GhcOptsModifications (g2 . g1) (p2 . p1)
175+
176+
instance Monoid GhcOptsModifications where
177+
mempty = GhcOptsModifications id id
178+
#endif
162179

163180
-- ---------------------------------------------------------------------
164181

@@ -177,7 +194,7 @@ data PluginDescriptor (ideState :: *) =
177194
, pluginHandlers :: PluginHandlers ideState
178195
, pluginConfigDescriptor :: ConfigDescriptor
179196
, pluginNotificationHandlers :: PluginNotificationHandlers ideState
180-
, pluginModifyDynflags :: DynFlagsModifications
197+
, pluginModifyDynflags :: GhcOptsModifications
181198
, pluginCli :: Maybe (ParserInfo (IdeCommand ideState))
182199
, pluginFileType :: [T.Text]
183200
-- ^ File extension of the files the plugin is responsible for.

0 commit comments

Comments
 (0)