Skip to content

Commit 7d87e3f

Browse files
committed
Change tracking of file types to language kinds
The plugin descriptor now tracks the language kinds it is responsible for instead of the file endings. We get the language kinds of any file from the VFS. Currently we are using a source repository to be able to use the lsp changes needed, but once lsp is released this can be removed.
1 parent b1966ff commit 7d87e3f

File tree

6 files changed

+60
-45
lines changed

6 files changed

+60
-45
lines changed

cabal.project

Lines changed: 11 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -7,6 +7,17 @@ packages:
77
./hls-plugin-api
88
./hls-test-utils
99

10+
source-repository-package
11+
type: git
12+
location: https://github.com/VeryMilkyJoe/lsp.git
13+
subdir: lsp
14+
tag: 39d780bbe9ebb4a21bd6d132a3c1abe4edf2b5a4
15+
16+
source-repository-package
17+
type: git
18+
location: https://github.com/VeryMilkyJoe/lsp.git
19+
subdir: lsp-test
20+
tag: 39d780bbe9ebb4a21bd6d132a3c1abe4edf2b5a4
1021

1122
index-state: 2025-05-12T13:26:29Z
1223

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

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -226,8 +226,8 @@ getVersionedTextDoc doc = do
226226
maybe (pure Nothing) getVirtualFile $
227227
uriToNormalizedFilePath $ toNormalizedUri uri
228228
let ver = case mvf of
229-
Just (VirtualFile lspver _ _) -> lspver
230-
Nothing -> 0
229+
Just (VirtualFile lspver _ _ _) -> lspver
230+
Nothing -> 0
231231
return (VersionedTextDocumentIdentifier uri ver)
232232

233233
fileStoreRules :: Recorder (WithPriority Log) -> (NormalizedFilePath -> Action Bool) -> Rules ()

ghcide/src/Development/IDE/Plugin/Completions/Logic.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -854,7 +854,7 @@ mergeListsBy cmp all_lists = merge_lists all_lists
854854

855855
-- |From the given cursor position, gets the prefix module or record for autocompletion
856856
getCompletionPrefix :: Position -> VFS.VirtualFile -> PosPrefixInfo
857-
getCompletionPrefix pos (VFS.VirtualFile _ _ ropetext) = getCompletionPrefixFromRope pos ropetext
857+
getCompletionPrefix pos (VFS.VirtualFile _ _ ropetext _) = getCompletionPrefixFromRope pos ropetext
858858

859859
getCompletionPrefixFromRope :: Position -> Rope.Rope -> PosPrefixInfo
860860
getCompletionPrefixFromRope pos@(Position l c) ropetext =

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

Lines changed: 4 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -251,11 +251,12 @@ extensiblePlugins recorder plugins = mempty { P.pluginHandlers = handlers }
251251
handlers = mconcat $ do
252252
(IdeMethod m :=> IdeHandler fs') <- DMap.assocs handlers'
253253
pure $ requestHandler m $ \ide params -> do
254+
vfs <- LSP.getVirtualFiles
254255
config <- Ide.PluginUtils.getClientConfig
255256
-- Only run plugins that are allowed to run on this request, save the
256257
-- list of disabled plugins incase that's all we have
257-
let (fs, dfs) = List.partition (\(_, desc, _) -> handlesRequest m params desc config == HandlesRequest) fs'
258-
let disabledPluginsReason = (\(x, desc, _) -> (x, handlesRequest m params desc config)) <$> dfs
258+
let (fs, dfs) = List.partition (\(_, desc, _) -> handlesRequest vfs m params desc config == HandlesRequest) fs'
259+
let disabledPluginsReason = (\(x, desc, _) -> (x, handlesRequest vfs m params desc config)) <$> dfs
259260
-- Clients generally don't display ResponseErrors so instead we log any that we come across
260261
-- However, some clients do display ResponseErrors! See for example the issues:
261262
-- https://github.com/haskell/haskell-language-server/issues/4467
@@ -370,7 +371,7 @@ extensibleNotificationPlugins recorder xs = mempty { P.pluginHandlers = handlers
370371
pure $ notificationHandler m $ \ide vfs params -> do
371372
config <- Ide.PluginUtils.getClientConfig
372373
-- Only run plugins that are enabled for this request
373-
let fs = filter (\(_, desc, _) -> handlesRequest m params desc config == HandlesRequest) fs'
374+
let fs = filter (\(_, desc, _) -> handlesRequest vfs m params desc config == HandlesRequest) fs'
374375
case nonEmpty fs of
375376
Nothing -> do
376377
logWith recorder Warning (LogNoPluginForMethod $ Some m)

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

Lines changed: 40 additions & 38 deletions
Original file line numberDiff line numberDiff line change
@@ -94,13 +94,13 @@ import Ide.Plugin.Properties
9494
import qualified Language.LSP.Protocol.Lens as L
9595
import Language.LSP.Protocol.Message
9696
import Language.LSP.Protocol.Types
97+
import qualified Language.LSP.Protocol.Types as J
9798
import Language.LSP.Server
9899
import Language.LSP.VFS
99100
import Numeric.Natural
100101
import OpenTelemetry.Eventlog
101102
import Options.Applicative (ParserInfo)
102103
import Prettyprinter as PP
103-
import System.FilePath
104104
import System.IO.Unsafe
105105
import Text.Regex.TDFA.Text ()
106106
import UnliftIO (MonadUnliftIO)
@@ -323,7 +323,7 @@ data PluginDescriptor (ideState :: Type) =
323323
, pluginNotificationHandlers :: PluginNotificationHandlers ideState
324324
, pluginModifyDynflags :: DynFlagsModifications
325325
, pluginCli :: Maybe (ParserInfo (IdeCommand ideState))
326-
, pluginFileType :: [T.Text]
326+
, pluginLanguageIds :: [J.LanguageKind]
327327
-- ^ File extension of the files the plugin is responsible for.
328328
-- The plugin is only allowed to handle files with these extensions.
329329
-- When writing handlers, etc. for this plugin it can be assumed that all handled files are of this type.
@@ -416,14 +416,14 @@ pluginResolverResponsible _ _ = DoesNotHandleRequest $ NotResolveOwner "(unable
416416
-- We are passing the msgParams here even though we only need the URI URI here.
417417
-- If in the future we need to be able to provide only an URI it can be
418418
-- separated again.
419-
pluginSupportsFileType :: (L.HasTextDocument m doc, L.HasUri doc Uri) => m -> PluginDescriptor c -> HandleRequestResult
420-
pluginSupportsFileType msgParams pluginDesc =
421-
case mfp of
422-
Just fp | T.pack (takeExtension fp) `elem` pluginFileType pluginDesc -> HandlesRequest
423-
_ -> DoesNotHandleRequest $ DoesNotSupportFileType (maybe "(unable to determine file type)" (T.pack . takeExtension) mfp)
419+
pluginSupportsFileType :: (L.HasTextDocument m doc, L.HasUri doc Uri) => VFS -> m -> PluginDescriptor c -> HandleRequestResult
420+
pluginSupportsFileType (VFS vfs) msgParams pluginDesc =
421+
case _language_id =<< mVFS of
422+
Just languageKind | languageKind `elem` pluginLanguageIds pluginDesc -> HandlesRequest
423+
_ -> DoesNotHandleRequest $ DoesNotSupportFileType (maybe "(unable to determine file type)" (T.pack . show) $ _language_id =<< mVFS)
424424
where
425-
mfp = uriToFilePath uri
426-
uri = msgParams ^. L.textDocument . L.uri
425+
mVFS = Map.lookup uri vfs
426+
uri = toNormalizedUri $ msgParams ^. L.textDocument . L.uri
427427

428428
-- | Methods that can be handled by plugins.
429429
-- 'ExtraParams' captures any extra data the IDE passes to the handlers for this method
@@ -452,7 +452,9 @@ class HasTracing (MessageParams m) => PluginMethod (k :: MessageKind) (m :: Meth
452452
--
453453
-- But there is no use to split it up into two different methods for now.
454454
handlesRequest
455-
:: SMethod m
455+
:: VFS
456+
-- ^ The virtual file system, contains the language kind of the file.
457+
-> SMethod m
456458
-- ^ Method type.
457459
-> MessageParams m
458460
-- ^ Whether a plugin is enabled might depend on the message parameters
@@ -468,24 +470,24 @@ class HasTracing (MessageParams m) => PluginMethod (k :: MessageKind) (m :: Meth
468470
-- with the given parameters?
469471

470472
default handlesRequest :: (L.HasTextDocument (MessageParams m) doc, L.HasUri doc Uri)
471-
=> SMethod m -> MessageParams m -> PluginDescriptor c -> Config -> HandleRequestResult
472-
handlesRequest _ params desc conf =
473-
pluginEnabledGlobally desc conf <> pluginSupportsFileType params desc
473+
=> VFS -> SMethod m -> MessageParams m -> PluginDescriptor c -> Config -> HandleRequestResult
474+
handlesRequest vfs _ params desc conf =
475+
pluginEnabledGlobally desc conf <> pluginSupportsFileType vfs params desc
474476

475477
-- | Check if a plugin is enabled, if one of it's specific config's is enabled,
476478
-- and if it supports the file
477479
pluginEnabledWithFeature :: (L.HasTextDocument (MessageParams m) doc, L.HasUri doc Uri)
478-
=> (PluginConfig -> Bool) -> SMethod m -> MessageParams m
480+
=> (PluginConfig -> Bool) -> VFS -> SMethod m -> MessageParams m
479481
-> PluginDescriptor c -> Config -> HandleRequestResult
480-
pluginEnabledWithFeature feature _ msgParams pluginDesc config =
482+
pluginEnabledWithFeature feature vfs _ msgParams pluginDesc config =
481483
pluginEnabledGlobally pluginDesc config
482484
<> pluginFeatureEnabled feature pluginDesc config
483-
<> pluginSupportsFileType msgParams pluginDesc
485+
<> pluginSupportsFileType vfs msgParams pluginDesc
484486

485487
-- | Check if a plugin is enabled, if one of it's specific configs is enabled,
486488
-- and if it's the plugin responsible for a resolve request.
487-
pluginEnabledResolve :: L.HasData_ s (Maybe Value) => (PluginConfig -> Bool) -> p -> s -> PluginDescriptor c -> Config -> HandleRequestResult
488-
pluginEnabledResolve feature _ msgParams pluginDesc config =
489+
pluginEnabledResolve :: L.HasData_ s (Maybe Value) => (PluginConfig -> Bool) -> VFS -> p -> s -> PluginDescriptor c -> Config -> HandleRequestResult
490+
pluginEnabledResolve feature _ _ msgParams pluginDesc config =
489491
pluginEnabledGlobally pluginDesc config
490492
<> pluginFeatureEnabled feature pluginDesc config
491493
<> pluginResolverResponsible msgParams pluginDesc
@@ -498,23 +500,23 @@ instance PluginMethod Request Method_CodeActionResolve where
498500
handlesRequest = pluginEnabledResolve plcCodeActionsOn
499501

500502
instance PluginMethod Request Method_TextDocumentDefinition where
501-
handlesRequest _ msgParams pluginDesc _ = pluginSupportsFileType msgParams pluginDesc
503+
handlesRequest vfs _ msgParams pluginDesc _ = pluginSupportsFileType vfs msgParams pluginDesc
502504

503505
instance PluginMethod Request Method_TextDocumentTypeDefinition where
504-
handlesRequest _ msgParams pluginDesc _ = pluginSupportsFileType msgParams pluginDesc
506+
handlesRequest vfs _ msgParams pluginDesc _ = pluginSupportsFileType vfs msgParams pluginDesc
505507

506508
instance PluginMethod Request Method_TextDocumentImplementation where
507-
handlesRequest _ msgParams pluginDesc _ = pluginSupportsFileType msgParams pluginDesc
509+
handlesRequest vfs _ msgParams pluginDesc _ = pluginSupportsFileType vfs msgParams pluginDesc
508510

509511
instance PluginMethod Request Method_TextDocumentDocumentHighlight where
510-
handlesRequest _ msgParams pluginDesc _ = pluginSupportsFileType msgParams pluginDesc
512+
handlesRequest vfs _ msgParams pluginDesc _ = pluginSupportsFileType vfs msgParams pluginDesc
511513

512514
instance PluginMethod Request Method_TextDocumentReferences where
513-
handlesRequest _ msgParams pluginDesc _ = pluginSupportsFileType msgParams pluginDesc
515+
handlesRequest vfs _ msgParams pluginDesc _ = pluginSupportsFileType vfs msgParams pluginDesc
514516

515517
instance PluginMethod Request Method_WorkspaceSymbol where
516518
-- Unconditionally enabled, but should it really be?
517-
handlesRequest _ _ _ _ = HandlesRequest
519+
handlesRequest _ _ _ _ _ = HandlesRequest
518520

519521
instance PluginMethod Request Method_TextDocumentInlayHint where
520522
handlesRequest = pluginEnabledWithFeature plcInlayHintsOn
@@ -549,22 +551,22 @@ instance PluginMethod Request Method_TextDocumentCompletion where
549551
handlesRequest = pluginEnabledWithFeature plcCompletionOn
550552

551553
instance PluginMethod Request Method_TextDocumentFormatting where
552-
handlesRequest _ msgParams pluginDesc conf =
554+
handlesRequest vfs _ msgParams pluginDesc conf =
553555
(if PluginId (formattingProvider conf) == pid
554556
|| PluginId (cabalFormattingProvider conf) == pid
555557
then HandlesRequest
556558
else DoesNotHandleRequest (NotFormattingProvider (formattingProvider conf)) )
557-
<> pluginSupportsFileType msgParams pluginDesc
559+
<> pluginSupportsFileType vfs msgParams pluginDesc
558560
where
559561
pid = pluginId pluginDesc
560562

561563
instance PluginMethod Request Method_TextDocumentRangeFormatting where
562-
handlesRequest _ msgParams pluginDesc conf =
564+
handlesRequest vfs _ msgParams pluginDesc conf =
563565
(if PluginId (formattingProvider conf) == pid
564566
|| PluginId (cabalFormattingProvider conf) == pid
565567
then HandlesRequest
566568
else DoesNotHandleRequest (NotFormattingProvider (formattingProvider conf)))
567-
<> pluginSupportsFileType msgParams pluginDesc
569+
<> pluginSupportsFileType vfs msgParams pluginDesc
568570
where
569571
pid = pluginId pluginDesc
570572

@@ -585,21 +587,21 @@ instance PluginMethod Request Method_TextDocumentFoldingRange where
585587

586588
instance PluginMethod Request Method_CallHierarchyIncomingCalls where
587589
-- This method has no URI parameter, thus no call to 'pluginResponsible'
588-
handlesRequest _ _ pluginDesc conf =
590+
handlesRequest _ _ _ pluginDesc conf =
589591
pluginEnabledGlobally pluginDesc conf
590592
<> pluginFeatureEnabled plcCallHierarchyOn pluginDesc conf
591593

592594
instance PluginMethod Request Method_CallHierarchyOutgoingCalls where
593595
-- This method has no URI parameter, thus no call to 'pluginResponsible'
594-
handlesRequest _ _ pluginDesc conf =
596+
handlesRequest _ _ _ pluginDesc conf =
595597
pluginEnabledGlobally pluginDesc conf
596598
<> pluginFeatureEnabled plcCallHierarchyOn pluginDesc conf
597599

598600
instance PluginMethod Request Method_WorkspaceExecuteCommand where
599-
handlesRequest _ _ _ _= HandlesRequest
601+
handlesRequest _ _ _ _ _ = HandlesRequest
600602

601603
instance PluginMethod Request (Method_CustomMethod m) where
602-
handlesRequest _ _ _ _ = HandlesRequest
604+
handlesRequest _ _ _ _ _ = HandlesRequest
603605

604606
-- Plugin Notifications
605607

@@ -613,19 +615,19 @@ instance PluginMethod Notification Method_TextDocumentDidClose where
613615

614616
instance PluginMethod Notification Method_WorkspaceDidChangeWatchedFiles where
615617
-- This method has no URI parameter, thus no call to 'pluginResponsible'.
616-
handlesRequest _ _ desc conf = pluginEnabledGlobally desc conf
618+
handlesRequest _ _ _ desc conf = pluginEnabledGlobally desc conf
617619

618620
instance PluginMethod Notification Method_WorkspaceDidChangeWorkspaceFolders where
619621
-- This method has no URI parameter, thus no call to 'pluginResponsible'.
620-
handlesRequest _ _ desc conf = pluginEnabledGlobally desc conf
622+
handlesRequest _ _ _ desc conf = pluginEnabledGlobally desc conf
621623

622624
instance PluginMethod Notification Method_WorkspaceDidChangeConfiguration where
623625
-- This method has no URI parameter, thus no call to 'pluginResponsible'.
624-
handlesRequest _ _ desc conf = pluginEnabledGlobally desc conf
626+
handlesRequest _ _ _ desc conf = pluginEnabledGlobally desc conf
625627

626628
instance PluginMethod Notification Method_Initialized where
627629
-- This method has no URI parameter, thus no call to 'pluginResponsible'.
628-
handlesRequest _ _ desc conf = pluginEnabledGlobally desc conf
630+
handlesRequest _ _ _ desc conf = pluginEnabledGlobally desc conf
629631

630632

631633
-- ---------------------------------------------------------------------
@@ -1054,7 +1056,7 @@ defaultPluginDescriptor plId desc =
10541056
mempty
10551057
mempty
10561058
Nothing
1057-
[".hs", ".lhs", ".hs-boot"]
1059+
[J.LanguageKind_Haskell, J.LanguageKind_Custom "literate haskell"]
10581060

10591061
-- | Set up a plugin descriptor, initialized with default values.
10601062
-- This plugin descriptor is prepared for @.cabal@ files and as such,
@@ -1075,7 +1077,7 @@ defaultCabalPluginDescriptor plId desc =
10751077
mempty
10761078
mempty
10771079
Nothing
1078-
[".cabal"]
1080+
[J.LanguageKind_Custom "cabal"]
10791081

10801082
newtype CommandId = CommandId T.Text
10811083
deriving (Show, Read, Eq, Ord)

plugins/hls-semantic-tokens-plugin/test/SemanticTokensTest.hs

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -29,6 +29,7 @@ import System.Info (compilerVersion)
2929
import Test.Hls
3030
import qualified Test.Hls.FileSystem as FS
3131
import Test.Hls.FileSystem (file, text)
32+
import qualified Language.LSP.Protocol.Types as J
3233

3334
testDataDir :: FilePath
3435
testDataDir = "plugins" </> "hls-semantic-tokens-plugin" </> "test" </> "testdata" </> testVersionDir
@@ -90,7 +91,7 @@ docLspSemanticTokensString :: (HasCallStack) => TextDocumentIdentifier -> Sessio
9091
docLspSemanticTokensString doc = do
9192
res <- Test.getSemanticTokens doc
9293
textContent <- documentContents doc
93-
let vfs = VirtualFile 0 0 (Rope.fromText textContent)
94+
let vfs = VirtualFile 0 0 (Rope.fromText textContent) $ Just J.LanguageKind_Haskell
9495
case res ^? Language.LSP.Protocol.Types._L of
9596
Just tokens -> do
9697
either (error . show) pure $ recoverLspSemanticTokens vfs tokens

0 commit comments

Comments
 (0)