Skip to content

Commit ea2f6eb

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 11bb99a commit ea2f6eb

File tree

8 files changed

+86
-49
lines changed

8 files changed

+86
-49
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: 33673596e1b2eb619ca38244e001adda880c3657
15+
16+
source-repository-package
17+
type: git
18+
location: https://github.com/VeryMilkyJoe/lsp.git
19+
subdir: lsp-test
20+
tag: 33673596e1b2eb619ca38244e001adda880c3657
1021

1122
index-state: 2025-06-07T14:57:40Z
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/Core/Rules.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -158,7 +158,7 @@ import Ide.Plugin.Properties (HasProperty,
158158
useProperty,
159159
usePropertyByPath)
160160
import Ide.Types (DynFlagsModifications (dynFlagsModifyGlobal, dynFlagsModifyParser),
161-
PluginId)
161+
PluginId, getVirtualFileFromVFS)
162162
import qualified Language.LSP.Protocol.Lens as JL
163163
import Language.LSP.Protocol.Message (SMethod (SMethod_CustomMethod, SMethod_WindowShowMessage))
164164
import Language.LSP.Protocol.Types (MessageType (MessageType_Info),
@@ -509,7 +509,7 @@ persistentHieFileRule recorder = addPersistentRule GetHieAst $ \file -> runMaybe
509509
res <- readHieFileForSrcFromDisk recorder file
510510
vfsRef <- asks vfsVar
511511
vfsData <- liftIO $ _vfsMap <$> readTVarIO vfsRef
512-
(currentSource, ver) <- liftIO $ case M.lookup (filePathToUri' file) vfsData of
512+
(currentSource, ver) <- liftIO $ case getVirtualFileFromVFS (VFS vfsData) (filePathToUri' file) of
513513
Nothing -> (,Nothing) . T.decodeUtf8 <$> BS.readFile (fromNormalizedFilePath file)
514514
Just vf -> pure (virtualFileText vf, Just $ virtualFileVersion vf)
515515
let refmap = Compat.generateReferencesMap . Compat.getAsts . Compat.hie_asts $ res

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

Lines changed: 3 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -129,6 +129,7 @@ import Development.IDE.Core.RuleTypes
129129
import Development.IDE.Types.Options as Options
130130
import qualified Language.LSP.Protocol.Message as LSP
131131
import qualified Language.LSP.Server as LSP
132+
import qualified Language.LSP.VFS as VFS
132133

133134
import Development.IDE.Core.Tracing
134135
import Development.IDE.Core.WorkerThread
@@ -394,7 +395,8 @@ class Typeable a => IsIdeGlobal a where
394395
getVirtualFile :: NormalizedFilePath -> Action (Maybe VirtualFile)
395396
getVirtualFile nf = do
396397
vfs <- fmap _vfsMap . liftIO . readTVarIO . vfsVar =<< getShakeExtras
397-
pure $! Map.lookup (filePathToUri' nf) vfs -- Don't leak a reference to the entire map
398+
pure $! -- Don't leak a reference to the entire map
399+
getVirtualFileFromVFS (VFS vfs) $ filePathToUri' nf
398400

399401
-- Take a snapshot of the current LSP VFS
400402
vfsSnapshot :: Maybe (LSP.LanguageContextEnv a) -> IO VFS

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: 6 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -49,9 +49,10 @@ import qualified Language.LSP.Server as LSP
4949
import Language.LSP.VFS
5050
import Prettyprinter.Render.String (renderString)
5151
import Text.Regex.TDFA.Text ()
52-
import UnliftIO (MonadUnliftIO, liftIO)
52+
import UnliftIO (MonadUnliftIO, liftIO, atomically)
5353
import UnliftIO.Async (forConcurrently)
5454
import UnliftIO.Exception (catchAny)
55+
import Control.Concurrent.STM.TVar (readTVar)
5556

5657
-- ---------------------------------------------------------------------
5758
--
@@ -251,11 +252,12 @@ extensiblePlugins recorder plugins = mempty { P.pluginHandlers = handlers }
251252
handlers = mconcat $ do
252253
(IdeMethod m :=> IdeHandler fs') <- DMap.assocs handlers'
253254
pure $ requestHandler m $ \ide params -> do
255+
vfs <- atomically $ readTVar $ vfsVar $ shakeExtras ide
254256
config <- Ide.PluginUtils.getClientConfig
255257
-- Only run plugins that are allowed to run on this request, save the
256258
-- 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
259+
let (fs, dfs) = List.partition (\(_, desc, _) -> handlesRequest vfs m params desc config == HandlesRequest) fs'
260+
let disabledPluginsReason = (\(x, desc, _) -> (x, handlesRequest vfs m params desc config)) <$> dfs
259261
-- Clients generally don't display ResponseErrors so instead we log any that we come across
260262
-- However, some clients do display ResponseErrors! See for example the issues:
261263
-- https://github.com/haskell/haskell-language-server/issues/4467
@@ -370,7 +372,7 @@ extensibleNotificationPlugins recorder xs = mempty { P.pluginHandlers = handlers
370372
pure $ notificationHandler m $ \ide vfs params -> do
371373
config <- Ide.PluginUtils.getClientConfig
372374
-- Only run plugins that are enabled for this request
373-
let fs = filter (\(_, desc, _) -> handlesRequest m params desc config == HandlesRequest) fs'
375+
let fs = filter (\(_, desc, _) -> handlesRequest vfs m params desc config == HandlesRequest) fs'
374376
case nonEmpty fs of
375377
Nothing -> do
376378
logWith recorder Warning (LogNoPluginForMethod $ Some m)

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

Lines changed: 59 additions & 38 deletions
Original file line numberDiff line numberDiff line change
@@ -39,6 +39,7 @@ module Ide.Types
3939
, PluginNotificationHandlers(..)
4040
, PluginRequestMethod(..)
4141
, getProcessID, getPid
42+
, getVirtualFileFromVFS
4243
, installSigUsr1Handler
4344
, lookupCommandProvider
4445
, ResolveFunction
@@ -94,13 +95,13 @@ import Ide.Plugin.Properties
9495
import qualified Language.LSP.Protocol.Lens as L
9596
import Language.LSP.Protocol.Message
9697
import Language.LSP.Protocol.Types
98+
import qualified Language.LSP.Protocol.Types as J
9799
import Language.LSP.Server
98100
import Language.LSP.VFS
99101
import Numeric.Natural
100102
import OpenTelemetry.Eventlog
101103
import Options.Applicative (ParserInfo)
102104
import Prettyprinter as PP
103-
import System.FilePath
104105
import System.IO.Unsafe
105106
import Text.Regex.TDFA.Text ()
106107
import UnliftIO (MonadUnliftIO)
@@ -323,7 +324,7 @@ data PluginDescriptor (ideState :: Type) =
323324
, pluginNotificationHandlers :: PluginNotificationHandlers ideState
324325
, pluginModifyDynflags :: DynFlagsModifications
325326
, pluginCli :: Maybe (ParserInfo (IdeCommand ideState))
326-
, pluginFileType :: [T.Text]
327+
, pluginLanguageIds :: [J.LanguageKind]
327328
-- ^ File extension of the files the plugin is responsible for.
328329
-- The plugin is only allowed to handle files with these extensions.
329330
-- When writing handlers, etc. for this plugin it can be assumed that all handled files are of this type.
@@ -416,14 +417,18 @@ pluginResolverResponsible _ _ = DoesNotHandleRequest $ NotResolveOwner "(unable
416417
-- We are passing the msgParams here even though we only need the URI URI here.
417418
-- If in the future we need to be able to provide only an URI it can be
418419
-- 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)
420+
pluginSupportsFileType :: (L.HasTextDocument m doc, L.HasUri doc Uri) => VFS -> m -> PluginDescriptor c -> HandleRequestResult
421+
pluginSupportsFileType (VFS vfs) msgParams pluginDesc =
422+
case languageKindM of
423+
Just languageKind | languageKind `elem` pluginLanguageIds pluginDesc -> HandlesRequest
424+
_ -> DoesNotHandleRequest $ DoesNotSupportFileType (maybe "(unable to determine file type)" (T.pack . show) languageKindM)
424425
where
425-
mfp = uriToFilePath uri
426-
uri = msgParams ^. L.textDocument . L.uri
426+
mVFE = getVirtualFileFromVFSIncludingClosed (VFS vfs) uri
427+
uri = toNormalizedUri $ msgParams ^. L.textDocument . L.uri
428+
languageKindM =
429+
case mVFE of
430+
Just x -> virtualFileEntryLanguageKind x
431+
_ -> Nothing
427432

428433
-- | Methods that can be handled by plugins.
429434
-- 'ExtraParams' captures any extra data the IDE passes to the handlers for this method
@@ -452,7 +457,9 @@ class HasTracing (MessageParams m) => PluginMethod (k :: MessageKind) (m :: Meth
452457
--
453458
-- But there is no use to split it up into two different methods for now.
454459
handlesRequest
455-
:: SMethod m
460+
:: VFS
461+
-- ^ The virtual file system, contains the language kind of the file.
462+
-> SMethod m
456463
-- ^ Method type.
457464
-> MessageParams m
458465
-- ^ Whether a plugin is enabled might depend on the message parameters
@@ -468,24 +475,24 @@ class HasTracing (MessageParams m) => PluginMethod (k :: MessageKind) (m :: Meth
468475
-- with the given parameters?
469476

470477
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
478+
=> VFS -> SMethod m -> MessageParams m -> PluginDescriptor c -> Config -> HandleRequestResult
479+
handlesRequest vfs _ params desc conf =
480+
pluginEnabledGlobally desc conf <> pluginSupportsFileType vfs params desc
474481

475482
-- | Check if a plugin is enabled, if one of it's specific config's is enabled,
476483
-- and if it supports the file
477484
pluginEnabledWithFeature :: (L.HasTextDocument (MessageParams m) doc, L.HasUri doc Uri)
478-
=> (PluginConfig -> Bool) -> SMethod m -> MessageParams m
485+
=> (PluginConfig -> Bool) -> VFS -> SMethod m -> MessageParams m
479486
-> PluginDescriptor c -> Config -> HandleRequestResult
480-
pluginEnabledWithFeature feature _ msgParams pluginDesc config =
487+
pluginEnabledWithFeature feature vfs _ msgParams pluginDesc config =
481488
pluginEnabledGlobally pluginDesc config
482489
<> pluginFeatureEnabled feature pluginDesc config
483-
<> pluginSupportsFileType msgParams pluginDesc
490+
<> pluginSupportsFileType vfs msgParams pluginDesc
484491

485492
-- | Check if a plugin is enabled, if one of it's specific configs is enabled,
486493
-- 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 =
494+
pluginEnabledResolve :: L.HasData_ s (Maybe Value) => (PluginConfig -> Bool) -> VFS -> p -> s -> PluginDescriptor c -> Config -> HandleRequestResult
495+
pluginEnabledResolve feature _ _ msgParams pluginDesc config =
489496
pluginEnabledGlobally pluginDesc config
490497
<> pluginFeatureEnabled feature pluginDesc config
491498
<> pluginResolverResponsible msgParams pluginDesc
@@ -498,23 +505,23 @@ instance PluginMethod Request Method_CodeActionResolve where
498505
handlesRequest = pluginEnabledResolve plcCodeActionsOn
499506

500507
instance PluginMethod Request Method_TextDocumentDefinition where
501-
handlesRequest _ msgParams pluginDesc _ = pluginSupportsFileType msgParams pluginDesc
508+
handlesRequest vfs _ msgParams pluginDesc _ = pluginSupportsFileType vfs msgParams pluginDesc
502509

503510
instance PluginMethod Request Method_TextDocumentTypeDefinition where
504-
handlesRequest _ msgParams pluginDesc _ = pluginSupportsFileType msgParams pluginDesc
511+
handlesRequest vfs _ msgParams pluginDesc _ = pluginSupportsFileType vfs msgParams pluginDesc
505512

506513
instance PluginMethod Request Method_TextDocumentImplementation where
507-
handlesRequest _ msgParams pluginDesc _ = pluginSupportsFileType msgParams pluginDesc
514+
handlesRequest vfs _ msgParams pluginDesc _ = pluginSupportsFileType vfs msgParams pluginDesc
508515

509516
instance PluginMethod Request Method_TextDocumentDocumentHighlight where
510-
handlesRequest _ msgParams pluginDesc _ = pluginSupportsFileType msgParams pluginDesc
517+
handlesRequest vfs _ msgParams pluginDesc _ = pluginSupportsFileType vfs msgParams pluginDesc
511518

512519
instance PluginMethod Request Method_TextDocumentReferences where
513-
handlesRequest _ msgParams pluginDesc _ = pluginSupportsFileType msgParams pluginDesc
520+
handlesRequest vfs _ msgParams pluginDesc _ = pluginSupportsFileType vfs msgParams pluginDesc
514521

515522
instance PluginMethod Request Method_WorkspaceSymbol where
516523
-- Unconditionally enabled, but should it really be?
517-
handlesRequest _ _ _ _ = HandlesRequest
524+
handlesRequest _ _ _ _ _ = HandlesRequest
518525

519526
instance PluginMethod Request Method_TextDocumentInlayHint where
520527
handlesRequest = pluginEnabledWithFeature plcInlayHintsOn
@@ -549,22 +556,22 @@ instance PluginMethod Request Method_TextDocumentCompletion where
549556
handlesRequest = pluginEnabledWithFeature plcCompletionOn
550557

551558
instance PluginMethod Request Method_TextDocumentFormatting where
552-
handlesRequest _ msgParams pluginDesc conf =
559+
handlesRequest vfs _ msgParams pluginDesc conf =
553560
(if PluginId (formattingProvider conf) == pid
554561
|| PluginId (cabalFormattingProvider conf) == pid
555562
then HandlesRequest
556563
else DoesNotHandleRequest (NotFormattingProvider (formattingProvider conf)) )
557-
<> pluginSupportsFileType msgParams pluginDesc
564+
<> pluginSupportsFileType vfs msgParams pluginDesc
558565
where
559566
pid = pluginId pluginDesc
560567

561568
instance PluginMethod Request Method_TextDocumentRangeFormatting where
562-
handlesRequest _ msgParams pluginDesc conf =
569+
handlesRequest vfs _ msgParams pluginDesc conf =
563570
(if PluginId (formattingProvider conf) == pid
564571
|| PluginId (cabalFormattingProvider conf) == pid
565572
then HandlesRequest
566573
else DoesNotHandleRequest (NotFormattingProvider (formattingProvider conf)))
567-
<> pluginSupportsFileType msgParams pluginDesc
574+
<> pluginSupportsFileType vfs msgParams pluginDesc
568575
where
569576
pid = pluginId pluginDesc
570577

@@ -585,21 +592,21 @@ instance PluginMethod Request Method_TextDocumentFoldingRange where
585592

586593
instance PluginMethod Request Method_CallHierarchyIncomingCalls where
587594
-- This method has no URI parameter, thus no call to 'pluginResponsible'
588-
handlesRequest _ _ pluginDesc conf =
595+
handlesRequest _ _ _ pluginDesc conf =
589596
pluginEnabledGlobally pluginDesc conf
590597
<> pluginFeatureEnabled plcCallHierarchyOn pluginDesc conf
591598

592599
instance PluginMethod Request Method_CallHierarchyOutgoingCalls where
593600
-- This method has no URI parameter, thus no call to 'pluginResponsible'
594-
handlesRequest _ _ pluginDesc conf =
601+
handlesRequest _ _ _ pluginDesc conf =
595602
pluginEnabledGlobally pluginDesc conf
596603
<> pluginFeatureEnabled plcCallHierarchyOn pluginDesc conf
597604

598605
instance PluginMethod Request Method_WorkspaceExecuteCommand where
599-
handlesRequest _ _ _ _= HandlesRequest
606+
handlesRequest _ _ _ _ _ = HandlesRequest
600607

601608
instance PluginMethod Request (Method_CustomMethod m) where
602-
handlesRequest _ _ _ _ = HandlesRequest
609+
handlesRequest _ _ _ _ _ = HandlesRequest
603610

604611
-- Plugin Notifications
605612

@@ -613,19 +620,19 @@ instance PluginMethod Notification Method_TextDocumentDidClose where
613620

614621
instance PluginMethod Notification Method_WorkspaceDidChangeWatchedFiles where
615622
-- This method has no URI parameter, thus no call to 'pluginResponsible'.
616-
handlesRequest _ _ desc conf = pluginEnabledGlobally desc conf
623+
handlesRequest _ _ _ desc conf = pluginEnabledGlobally desc conf
617624

618625
instance PluginMethod Notification Method_WorkspaceDidChangeWorkspaceFolders where
619626
-- This method has no URI parameter, thus no call to 'pluginResponsible'.
620-
handlesRequest _ _ desc conf = pluginEnabledGlobally desc conf
627+
handlesRequest _ _ _ desc conf = pluginEnabledGlobally desc conf
621628

622629
instance PluginMethod Notification Method_WorkspaceDidChangeConfiguration where
623630
-- This method has no URI parameter, thus no call to 'pluginResponsible'.
624-
handlesRequest _ _ desc conf = pluginEnabledGlobally desc conf
631+
handlesRequest _ _ _ desc conf = pluginEnabledGlobally desc conf
625632

626633
instance PluginMethod Notification Method_Initialized where
627634
-- This method has no URI parameter, thus no call to 'pluginResponsible'.
628-
handlesRequest _ _ desc conf = pluginEnabledGlobally desc conf
635+
handlesRequest _ _ _ desc conf = pluginEnabledGlobally desc conf
629636

630637

631638
-- ---------------------------------------------------------------------
@@ -1054,7 +1061,7 @@ defaultPluginDescriptor plId desc =
10541061
mempty
10551062
mempty
10561063
Nothing
1057-
[".hs", ".lhs", ".hs-boot"]
1064+
[J.LanguageKind_Haskell, J.LanguageKind_Custom "literate haskell"]
10581065

10591066
-- | Set up a plugin descriptor, initialized with default values.
10601067
-- This plugin descriptor is prepared for @.cabal@ files and as such,
@@ -1075,7 +1082,7 @@ defaultCabalPluginDescriptor plId desc =
10751082
mempty
10761083
mempty
10771084
Nothing
1078-
[".cabal"]
1085+
[J.LanguageKind_Custom "cabal"]
10791086

10801087
newtype CommandId = CommandId T.Text
10811088
deriving (Show, Read, Eq, Ord)
@@ -1251,6 +1258,20 @@ mkLspCmdId pid (PluginId plid) (CommandId cid)
12511258
getPid :: IO T.Text
12521259
getPid = T.pack . show <$> getProcessID
12531260

1261+
getVirtualFileFromVFS :: VFS -> NormalizedUri -> Maybe VirtualFile
1262+
getVirtualFileFromVFS (VFS vfs) uri =
1263+
case Map.lookup uri vfs of
1264+
Just (Open x) -> Just x
1265+
Just (Closed _) -> Nothing
1266+
Nothing -> Nothing
1267+
1268+
getVirtualFileFromVFSIncludingClosed :: VFS -> NormalizedUri -> Maybe VirtualFileEntry
1269+
getVirtualFileFromVFSIncludingClosed (VFS vfs) uri =
1270+
case Map.lookup uri vfs of
1271+
Just x -> Just x
1272+
Nothing -> Nothing
1273+
1274+
12541275
getProcessID :: IO Int
12551276
installSigUsr1Handler :: IO () -> IO ()
12561277

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

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -22,6 +22,7 @@ import Ide.Plugin.SemanticTokens.Types
2222
import Ide.Types
2323
import qualified Language.LSP.Protocol.Lens as L
2424
import Language.LSP.Protocol.Types
25+
import qualified Language.LSP.Protocol.Types as J
2526
import qualified Language.LSP.Test as Test
2627
import Language.LSP.VFS (VirtualFile (..))
2728
import System.FilePath
@@ -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)