Skip to content

Commit eebf3b0

Browse files
committed
Enable notification handlers only for Haskell files
1 parent 86d8f28 commit eebf3b0

File tree

4 files changed

+38
-19
lines changed

4 files changed

+38
-19
lines changed

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

+6-2
Original file line numberDiff line numberDiff line change
@@ -23,6 +23,7 @@ import qualified Language.LSP.Server as LSP
2323
import Language.LSP.Types
2424

2525
import qualified Data.Text as T
26+
import System.FilePath
2627

2728
gotoDefinition :: IdeState -> TextDocumentPositionParams -> LSP.LspM c (Either ResponseError (ResponseResult TextDocumentDefinition))
2829
hover :: IdeState -> TextDocumentPositionParams -> LSP.LspM c (Either ResponseError (Maybe Hover))
@@ -76,8 +77,11 @@ request
7677
-> LSP.LspM c (Either ResponseError b)
7778
request label getResults notFound found ide (TextDocumentPositionParams (TextDocumentIdentifier uri) pos) = liftIO $ do
7879
mbResult <- case uriToFilePath' uri of
79-
Just path -> logAndRunRequest label getResults ide pos path
80-
Nothing -> pure Nothing
80+
Just path
81+
| takeExtension path `elem` [".hs", ".lhs"]
82+
-> logAndRunRequest label getResults ide pos path
83+
| otherwise -> pure Nothing
84+
Nothing -> pure Nothing
8185
pure $ Right $ maybe notFound found mbResult
8286

8387
logAndRunRequest :: T.Text -> (NormalizedFilePath -> Position -> IdeAction b) -> IdeState -> Position -> String -> IO b

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

+1-1
Original file line numberDiff line numberDiff line change
@@ -40,7 +40,7 @@ import Ide.Plugin.Config (CheckParents (CheckOnClo
4040
import Ide.Types
4141
import System.FilePath (takeExtension)
4242

43-
whenUriHaskellFile :: Uri -> (NormalizedFilePath -> IO ()) -> IO ()
43+
whenUriHaskellFile :: MonadIO m => Uri -> (NormalizedFilePath -> m ()) -> m ()
4444
whenUriHaskellFile uri act = whenJust maybeHaskellFile $ act . toNormalizedFilePath'
4545
where
4646
maybeHaskellFile = do

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

+29-14
Original file line numberDiff line numberDiff line change
@@ -147,7 +147,7 @@ executeCommandHandlers ecs = requestHandler SWorkspaceExecuteCommand execCmd
147147
extensiblePlugins :: [(PluginId, PluginDescriptor IdeState)] -> Plugin Config
148148
extensiblePlugins xs = mempty { P.pluginHandlers = handlers }
149149
where
150-
getPluginDescriptor pid = fromJust $ lookup pid xs
150+
getPluginDescriptor pid = lookup pid xs
151151
IdeHandlers handlers' = foldMap bakePluginId xs
152152
bakePluginId :: (PluginId, PluginDescriptor IdeState) -> IdeHandlers
153153
bakePluginId (pid,pluginDesc) = IdeHandlers $ DMap.map
@@ -159,20 +159,35 @@ extensiblePlugins xs = mempty { P.pluginHandlers = handlers }
159159
(IdeMethod m :=> IdeHandler fs') <- DMap.assocs handlers'
160160
pure $ requestHandler m $ \ide params -> do
161161
config <- Ide.PluginUtils.getClientConfig
162-
let fs = filter (\(pid,_) -> pluginEnabled m params (getPluginDescriptor pid) config) fs'
163-
case nonEmpty fs of
164-
Nothing -> pure $ Left $ ResponseError InvalidRequest
165-
("No plugin enabled for " <> T.pack (show m) <> ", available: " <> T.pack (show $ map fst fs))
162+
let pluginInfo = map (\(pid,_) -> (pid, getPluginDescriptor pid)) fs'
163+
cleanPluginInfo <- go pluginInfo []
164+
case cleanPluginInfo of
165+
Left err -> pure $ Left err
166+
Right pluginInfos -> do
167+
let fs = map snd $ filter (\((_, desc), _) -> pluginEnabled m params desc config) (zip pluginInfos fs')
168+
case nonEmpty fs of
169+
Nothing -> pure $ Left $ ResponseError InvalidRequest
170+
("No plugin enabled for " <> T.pack (show m) <> ", available: " <> T.pack (show $ map fst fs))
171+
Nothing
172+
Just fs -> do
173+
let msg e pid = "Exception in plugin " <> T.pack (show pid) <> "while processing " <> T.pack (show m) <> ": " <> T.pack (show e)
174+
es <- runConcurrently msg (show m) fs ide params
175+
let (errs,succs) = partitionEithers $ toList es
176+
case nonEmpty succs of
177+
Nothing -> pure $ Left $ combineErrors errs
178+
Just xs -> do
179+
caps <- LSP.getClientCapabilities
180+
pure $ Right $ combineResponses m config caps params xs
181+
182+
go :: [(PluginId, Maybe (PluginDescriptor c))] -> [(PluginId, PluginDescriptor c)] -> LSP.LspM Config (Either ResponseError [(PluginId, PluginDescriptor c)])
183+
go ((pid, Nothing):_) _ = pure $ Left $ ResponseError InvalidRequest
184+
("No plugindescriptor found for " <> pidT <> ", available: ")
166185
Nothing
167-
Just fs -> do
168-
let msg e pid = "Exception in plugin " <> T.pack (show pid) <> "while processing " <> T.pack (show m) <> ": " <> T.pack (show e)
169-
es <- runConcurrently msg (show m) fs ide params
170-
let (errs,succs) = partitionEithers $ toList es
171-
case nonEmpty succs of
172-
Nothing -> pure $ Left $ combineErrors errs
173-
Just xs -> do
174-
caps <- LSP.getClientCapabilities
175-
pure $ Right $ combineResponses m config caps params xs
186+
where
187+
PluginId pidT = pid
188+
go ((pid, Just desc):xs) ys = go xs (ys ++ [(pid, desc)])
189+
go [] ys = pure $ Right ys
190+
176191
-- ---------------------------------------------------------------------
177192

178193
extensibleNotificationPlugins :: [(PluginId, PluginNotificationHandlers IdeState)] -> Plugin Config

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

+2-2
Original file line numberDiff line numberDiff line change
@@ -403,7 +403,7 @@ defaultPluginDescriptor plId =
403403
mempty
404404
mempty
405405
Nothing
406-
["hs", "lhs"]
406+
[".hs", ".lhs"]
407407

408408
defaultCabalPluginDescriptor :: PluginId -> PluginDescriptor ideState
409409
defaultCabalPluginDescriptor plId =
@@ -416,7 +416,7 @@ defaultCabalPluginDescriptor plId =
416416
mempty
417417
mempty
418418
Nothing
419-
["cabal"]
419+
[".cabal"]
420420

421421
newtype CommandId = CommandId T.Text
422422
deriving (Show, Read, Eq, Ord)

0 commit comments

Comments
 (0)