Skip to content

Commit ffb0563

Browse files
Workspace roots and getFileExists (#412)
* parse lsp client configuration to track workspace roots * Only use Watched files on workspace files * Apply suggestions from code review Co-Authored-By: Moritz Kiefer <moritz.kiefer@purelyfunctional.org> * Add tests for watched files Left as future work: adding tests for workspace folder notifications * Add a test for file creation outside workspace Co-authored-by: Moritz Kiefer <moritz.kiefer@purelyfunctional.org>
1 parent 2d71599 commit ffb0563

File tree

12 files changed

+159
-27
lines changed

12 files changed

+159
-27
lines changed

ghcide.cabal

+1
Original file line numberDiff line numberDiff line change
@@ -101,6 +101,7 @@ library
101101
exposed-modules:
102102
Development.IDE.Core.Debouncer
103103
Development.IDE.Core.FileStore
104+
Development.IDE.Core.IdeConfiguration
104105
Development.IDE.Core.OfInterest
105106
Development.IDE.Core.PositionMapping
106107
Development.IDE.Core.Rules

src/Development/IDE/Core/FileExists.hs

+11-2
Original file line numberDiff line numberDiff line change
@@ -19,6 +19,7 @@ import qualified Data.HashMap.Strict as HashMap
1919
import Data.Maybe
2020
import qualified Data.Text as T
2121
import Development.IDE.Core.FileStore
22+
import Development.IDE.Core.IdeConfiguration
2223
import Development.IDE.Core.Shake
2324
import Development.IDE.Types.Location
2425
import Development.Shake
@@ -101,6 +102,11 @@ fileExistsRulesFast :: IO LspId -> VFSHandle -> Rules ()
101102
fileExistsRulesFast getLspId vfs = do
102103
addIdeGlobal . FileExistsMapVar =<< liftIO (newVar [])
103104
defineEarlyCutoff $ \GetFileExists file -> do
105+
isWf <- isWorkspaceFile file
106+
if isWf then fileExistsFast getLspId vfs file else fileExistsSlow vfs file
107+
108+
fileExistsFast :: IO LspId -> VFSHandle -> NormalizedFilePath -> Action (Maybe BS.ByteString, ([a], Maybe Bool))
109+
fileExistsFast getLspId vfs file = do
104110
fileExistsMap <- getFileExistsMapUntracked
105111
let mbFilesWatched = HashMap.lookup file fileExistsMap
106112
case mbFilesWatched of
@@ -145,8 +151,11 @@ summarizeExists :: Bool -> Maybe BS.ByteString
145151
summarizeExists x = Just $ if x then BS.singleton 1 else BS.empty
146152

147153
fileExistsRulesSlow:: VFSHandle -> Rules ()
148-
fileExistsRulesSlow vfs = do
149-
defineEarlyCutoff $ \GetFileExists file -> do
154+
fileExistsRulesSlow vfs =
155+
defineEarlyCutoff $ \GetFileExists file -> fileExistsSlow vfs file
156+
157+
fileExistsSlow :: VFSHandle -> NormalizedFilePath -> Action (Maybe BS.ByteString, ([a], Maybe Bool))
158+
fileExistsSlow vfs file = do
150159
alwaysRerun
151160
exist <- liftIO $ getFileExistsVFS vfs file
152161
pure (summarizeExists exist, ([], Just exist))
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,66 @@
1+
{-# LANGUAGE DuplicateRecordFields #-}
2+
module Development.IDE.Core.IdeConfiguration
3+
( IdeConfiguration(..)
4+
, registerIdeConfiguration
5+
, parseConfiguration
6+
, parseWorkspaceFolder
7+
, isWorkspaceFile
8+
, modifyWorkspaceFolders
9+
)
10+
where
11+
12+
import Control.Concurrent.Extra
13+
import Control.Monad
14+
import Data.HashSet (HashSet, singleton)
15+
import Data.Text (Text, isPrefixOf)
16+
import Development.IDE.Core.Shake
17+
import Development.IDE.Types.Location
18+
import Development.Shake
19+
import Language.Haskell.LSP.Types
20+
21+
-- | Lsp client relevant configuration details
22+
data IdeConfiguration = IdeConfiguration
23+
{ workspaceFolders :: HashSet NormalizedUri
24+
}
25+
deriving (Show)
26+
27+
newtype IdeConfigurationVar = IdeConfigurationVar {unIdeConfigurationRef :: Var IdeConfiguration}
28+
29+
instance IsIdeGlobal IdeConfigurationVar
30+
31+
registerIdeConfiguration :: ShakeExtras -> IdeConfiguration -> IO ()
32+
registerIdeConfiguration extras =
33+
addIdeGlobalExtras extras . IdeConfigurationVar <=< newVar
34+
35+
getIdeConfiguration :: Action IdeConfiguration
36+
getIdeConfiguration =
37+
getIdeGlobalAction >>= liftIO . readVar . unIdeConfigurationRef
38+
39+
parseConfiguration :: InitializeRequest -> IdeConfiguration
40+
parseConfiguration RequestMessage { _params = InitializeParams {..} } =
41+
IdeConfiguration { .. }
42+
where
43+
workspaceFolders =
44+
foldMap (singleton . toNormalizedUri) _rootUri
45+
<> (foldMap . foldMap)
46+
(singleton . parseWorkspaceFolder)
47+
_workspaceFolders
48+
49+
parseWorkspaceFolder :: WorkspaceFolder -> NormalizedUri
50+
parseWorkspaceFolder =
51+
toNormalizedUri . Uri . (_uri :: WorkspaceFolder -> Text)
52+
53+
modifyWorkspaceFolders
54+
:: IdeState -> (HashSet NormalizedUri -> HashSet NormalizedUri) -> IO ()
55+
modifyWorkspaceFolders ide f = do
56+
IdeConfigurationVar var <- getIdeGlobalState ide
57+
IdeConfiguration ws <- readVar var
58+
writeVar var (IdeConfiguration (f ws))
59+
60+
isWorkspaceFile :: NormalizedFilePath -> Action Bool
61+
isWorkspaceFile file = do
62+
IdeConfiguration {..} <- getIdeConfiguration
63+
let toText = getUri . fromNormalizedUri
64+
return $ any
65+
(\root -> toText root `isPrefixOf` toText (filePathToUri' file))
66+
workspaceFolders

src/Development/IDE/Core/Shake.hs

+8-6
Original file line numberDiff line numberDiff line change
@@ -19,7 +19,7 @@
1919
-- always stored as real Haskell values, whereas Shake serialises all 'A' values
2020
-- between runs. To deserialise a Shake value, we just consult Values.
2121
module Development.IDE.Core.Shake(
22-
IdeState,
22+
IdeState, shakeExtras,
2323
ShakeExtras(..), getShakeExtras,
2424
IdeRule, IdeResult, GetModificationTime(..),
2525
shakeOpen, shakeShut,
@@ -30,7 +30,7 @@ module Development.IDE.Core.Shake(
3030
define, defineEarlyCutoff, defineOnDisk, needOnDisk, needOnDisks,
3131
getDiagnostics, unsafeClearDiagnostics,
3232
getHiddenDiagnostics,
33-
IsIdeGlobal, addIdeGlobal, getIdeGlobalState, getIdeGlobalAction,
33+
IsIdeGlobal, addIdeGlobal, addIdeGlobalExtras, getIdeGlobalState, getIdeGlobalAction,
3434
garbageCollect,
3535
setPriority,
3636
sendEvent,
@@ -114,13 +114,15 @@ getShakeExtrasRules = do
114114
Just x <- getShakeExtraRules @ShakeExtras
115115
return x
116116

117-
118-
119117
class Typeable a => IsIdeGlobal a where
120118

121119
addIdeGlobal :: IsIdeGlobal a => a -> Rules ()
122-
addIdeGlobal x@(typeOf -> ty) = do
123-
ShakeExtras{globals} <- getShakeExtrasRules
120+
addIdeGlobal x = do
121+
extras <- getShakeExtrasRules
122+
liftIO $ addIdeGlobalExtras extras x
123+
124+
addIdeGlobalExtras :: IsIdeGlobal a => ShakeExtras -> a -> IO ()
125+
addIdeGlobalExtras ShakeExtras{globals} x@(typeOf -> ty) =
124126
liftIO $ modifyVar_ globals $ \mp -> case HMap.lookup ty mp of
125127
Just _ -> error $ "Can't addIdeGlobal twice on the same type, got " ++ show ty
126128
Nothing -> return $! HMap.insert ty (toDyn x) mp

src/Development/IDE/LSP/LanguageServer.hs

+12-7
Original file line numberDiff line numberDiff line change
@@ -28,10 +28,11 @@ import GHC.IO.Handle (hDuplicate)
2828
import System.IO
2929
import Control.Monad.Extra
3030

31+
import Development.IDE.Core.IdeConfiguration
32+
import Development.IDE.Core.Shake
3133
import Development.IDE.LSP.HoverDefinition
3234
import Development.IDE.LSP.Notifications
3335
import Development.IDE.LSP.Outline
34-
import Development.IDE.Core.Service
3536
import Development.IDE.Types.Logger
3637
import Development.IDE.Core.FileStore
3738
import Language.Haskell.LSP.Core (LspFuncs(..))
@@ -105,8 +106,8 @@ runLanguageServer options userHandlers getIdeState = do
105106
handlers <- parts WithMessage{withResponse, withNotification, withResponseAndRequest} def
106107

107108
let initializeCallbacks = LSP.InitializeCallbacks
108-
{ LSP.onInitialConfiguration = const $ Right ()
109-
, LSP.onConfigurationChange = const $ Right ()
109+
{ LSP.onInitialConfiguration = Right . parseConfiguration
110+
, LSP.onConfigurationChange = const $ Left "Configuration changes not supported yet"
110111
, LSP.onStartup = handleInit (signalBarrier clientMsgBarrier ()) clearReqId waitForCancel clientMsgChan
111112
}
112113

@@ -121,9 +122,13 @@ runLanguageServer options userHandlers getIdeState = do
121122
, void $ waitBarrier clientMsgBarrier
122123
]
123124
where
124-
handleInit :: IO () -> (LspId -> IO ()) -> (LspId -> IO ()) -> Chan Message -> LSP.LspFuncs () -> IO (Maybe err)
125+
handleInit :: IO () -> (LspId -> IO ()) -> (LspId -> IO ()) -> Chan Message -> LSP.LspFuncs IdeConfiguration -> IO (Maybe err)
125126
handleInit exitClientMsg clearReqId waitForCancel clientMsgChan lspFuncs@LSP.LspFuncs{..} = do
127+
126128
ide <- getIdeState getNextReqId sendFunc (makeLSPVFSHandle lspFuncs) clientCapabilities
129+
130+
mapM_ (registerIdeConfiguration (shakeExtras ide)) =<< config
131+
127132
_ <- flip forkFinally (const exitClientMsg) $ forever $ do
128133
msg <- readChan clientMsgChan
129134
case msg of
@@ -193,12 +198,12 @@ cancelHandler cancelRequest = PartialHandlers $ \_ x -> return x
193198
-- | A message that we need to deal with - the pieces are split up with existentials to gain additional type safety
194199
-- and defer precise processing until later (allows us to keep at a higher level of abstraction slightly longer)
195200
data Message
196-
= forall m req resp . (Show m, Show req) => Response (RequestMessage m req resp) (ResponseMessage resp -> FromServerMessage) (LSP.LspFuncs () -> IdeState -> req -> IO (Either ResponseError resp))
201+
= forall m req resp . (Show m, Show req) => Response (RequestMessage m req resp) (ResponseMessage resp -> FromServerMessage) (LSP.LspFuncs IdeConfiguration -> IdeState -> req -> IO (Either ResponseError resp))
197202
-- | Used for cases in which we need to send not only a response,
198203
-- but also an additional request to the client.
199204
-- For example, 'executeCommand' may generate an 'applyWorkspaceEdit' request.
200-
| forall m rm req resp newReqParams newReqBody . (Show m, Show rm, Show req) => ResponseAndRequest (RequestMessage m req resp) (ResponseMessage resp -> FromServerMessage) (RequestMessage rm newReqParams newReqBody -> FromServerMessage) (LSP.LspFuncs () -> IdeState -> req -> IO (resp, Maybe (rm, newReqParams)))
201-
| forall m req . (Show m, Show req) => Notification (NotificationMessage m req) (LSP.LspFuncs () -> IdeState -> req -> IO ())
205+
| forall m rm req resp newReqParams newReqBody . (Show m, Show rm, Show req) => ResponseAndRequest (RequestMessage m req resp) (ResponseMessage resp -> FromServerMessage) (RequestMessage rm newReqParams newReqBody -> FromServerMessage) (LSP.LspFuncs IdeConfiguration -> IdeState -> req -> IO (resp, Maybe (rm, newReqParams)))
206+
| forall m req . (Show m, Show req) => Notification (NotificationMessage m req) (LSP.LspFuncs IdeConfiguration -> IdeState -> req -> IO ())
202207

203208

204209
modifyOptions :: LSP.Options -> LSP.Options

src/Development/IDE/LSP/Notifications.hs

+8
Original file line numberDiff line numberDiff line change
@@ -13,6 +13,7 @@ import qualified Language.Haskell.LSP.Core as LSP
1313
import Language.Haskell.LSP.Types
1414
import qualified Language.Haskell.LSP.Types as LSP
1515

16+
import Development.IDE.Core.IdeConfiguration
1617
import Development.IDE.Core.Service
1718
import Development.IDE.Types.Location
1819
import Development.IDE.Types.Logger
@@ -69,4 +70,11 @@ setHandlersNotifications = PartialHandlers $ \WithMessage{..} x -> return x
6970
logInfo (ideLogger ide) $ "Files created or deleted: " <> msg
7071
modifyFileExists ide events
7172
setSomethingModified ide
73+
,LSP.didChangeWorkspaceFoldersNotificationHandler = withNotification (LSP.didChangeWorkspaceFoldersNotificationHandler x) $
74+
\_ ide (DidChangeWorkspaceFoldersParams events) -> do
75+
let add = S.union
76+
substract = flip S.difference
77+
modifyWorkspaceFolders ide
78+
$ add (foldMap (S.singleton . parseWorkspaceFolder) (_added events))
79+
. substract (foldMap (S.singleton . parseWorkspaceFolder) (_removed events))
7280
}

src/Development/IDE/LSP/Outline.hs

+2-1
Original file line numberDiff line numberDiff line change
@@ -18,6 +18,7 @@ import Data.Text ( Text
1818
)
1919
import qualified Data.Text as T
2020
import Development.IDE.Core.Rules
21+
import Development.IDE.Core.IdeConfiguration
2122
import Development.IDE.Core.Shake
2223
import Development.IDE.GHC.Compat
2324
import Development.IDE.GHC.Error ( srcSpanToRange )
@@ -34,7 +35,7 @@ setHandlersOutline = PartialHandlers $ \WithMessage {..} x -> return x
3435
}
3536

3637
moduleOutline
37-
:: LSP.LspFuncs () -> IdeState -> DocumentSymbolParams -> IO (Either ResponseError DSResult)
38+
:: LSP.LspFuncs IdeConfiguration -> IdeState -> DocumentSymbolParams -> IO (Either ResponseError DSResult)
3839
moduleOutline _lsp ideState DocumentSymbolParams { _textDocument = TextDocumentIdentifier uri }
3940
= case uriToFilePath uri of
4041
Just (toNormalizedFilePath -> fp) -> do

src/Development/IDE/LSP/Server.hs

+4-3
Original file line numberDiff line numberDiff line change
@@ -14,22 +14,23 @@ import Data.Default
1414
import Language.Haskell.LSP.Types
1515
import qualified Language.Haskell.LSP.Core as LSP
1616
import qualified Language.Haskell.LSP.Messages as LSP
17+
import Development.IDE.Core.IdeConfiguration
1718
import Development.IDE.Core.Service
1819

1920
data WithMessage = WithMessage
2021
{withResponse :: forall m req resp . (Show m, Show req) =>
2122
(ResponseMessage resp -> LSP.FromServerMessage) -> -- how to wrap a response
22-
(LSP.LspFuncs () -> IdeState -> req -> IO (Either ResponseError resp)) -> -- actual work
23+
(LSP.LspFuncs IdeConfiguration -> IdeState -> req -> IO (Either ResponseError resp)) -> -- actual work
2324
Maybe (LSP.Handler (RequestMessage m req resp))
2425
,withNotification :: forall m req . (Show m, Show req) =>
2526
Maybe (LSP.Handler (NotificationMessage m req)) -> -- old notification handler
26-
(LSP.LspFuncs () -> IdeState -> req -> IO ()) -> -- actual work
27+
(LSP.LspFuncs IdeConfiguration -> IdeState -> req -> IO ()) -> -- actual work
2728
Maybe (LSP.Handler (NotificationMessage m req))
2829
,withResponseAndRequest :: forall m rm req resp newReqParams newReqBody.
2930
(Show m, Show rm, Show req, Show newReqParams, Show newReqBody) =>
3031
(ResponseMessage resp -> LSP.FromServerMessage) -> -- how to wrap a response
3132
(RequestMessage rm newReqParams newReqBody -> LSP.FromServerMessage) -> -- how to wrap the additional req
32-
(LSP.LspFuncs () -> IdeState -> req -> IO (resp, Maybe (rm, newReqParams))) -> -- actual work
33+
(LSP.LspFuncs IdeConfiguration -> IdeState -> req -> IO (resp, Maybe (rm, newReqParams))) -> -- actual work
3334
Maybe (LSP.Handler (RequestMessage m req resp))
3435
}
3536

src/Development/IDE/Plugin.hs

+2-1
Original file line numberDiff line numberDiff line change
@@ -7,6 +7,7 @@ import Development.IDE.LSP.Server
77

88
import Language.Haskell.LSP.Types
99
import Development.IDE.Core.Rules
10+
import Development.IDE.Core.IdeConfiguration
1011
import qualified Language.Haskell.LSP.Core as LSP
1112
import Language.Haskell.LSP.Messages
1213

@@ -26,7 +27,7 @@ instance Monoid Plugin where
2627
mempty = def
2728

2829

29-
codeActionPlugin :: (LSP.LspFuncs () -> IdeState -> TextDocumentIdentifier -> Range -> CodeActionContext -> IO (Either ResponseError [CAResult])) -> Plugin
30+
codeActionPlugin :: (LSP.LspFuncs IdeConfiguration -> IdeState -> TextDocumentIdentifier -> Range -> CodeActionContext -> IO (Either ResponseError [CAResult])) -> Plugin
3031
codeActionPlugin f = Plugin mempty $ PartialHandlers $ \WithMessage{..} x -> return x{
3132
LSP.codeActionHandler = withResponse RspCodeAction g
3233
}

src/Development/IDE/Plugin/CodeAction.hs

+4-3
Original file line numberDiff line numberDiff line change
@@ -12,6 +12,7 @@ import Language.Haskell.LSP.Types
1212
import Control.Monad (join)
1313
import Development.IDE.Plugin
1414
import Development.IDE.GHC.Compat
15+
import Development.IDE.Core.IdeConfiguration
1516
import Development.IDE.Core.Rules
1617
import Development.IDE.Core.RuleTypes
1718
import Development.IDE.Core.Service
@@ -43,7 +44,7 @@ plugin = codeActionPlugin codeAction <> Plugin mempty setHandlersCodeLens
4344

4445
-- | Generate code actions.
4546
codeAction
46-
:: LSP.LspFuncs ()
47+
:: LSP.LspFuncs IdeConfiguration
4748
-> IdeState
4849
-> TextDocumentIdentifier
4950
-> Range
@@ -65,7 +66,7 @@ codeAction lsp state (TextDocumentIdentifier uri) _range CodeActionContext{_diag
6566

6667
-- | Generate code lenses.
6768
codeLens
68-
:: LSP.LspFuncs ()
69+
:: LSP.LspFuncs IdeConfiguration
6970
-> IdeState
7071
-> CodeLensParams
7172
-> IO (Either ResponseError (List CodeLens))
@@ -86,7 +87,7 @@ codeLens _lsp ideState CodeLensParams{_textDocument=TextDocumentIdentifier uri}
8687

8788
-- | Execute the "typesignature.add" command.
8889
executeAddSignatureCommand
89-
:: LSP.LspFuncs ()
90+
:: LSP.LspFuncs IdeConfiguration
9091
-> IdeState
9192
-> ExecuteCommandParams
9293
-> IO (Value, Maybe (ServerMethod, ApplyWorkspaceEditParams))

src/Development/IDE/Plugin/Completions.hs

+2-1
Original file line numberDiff line numberDiff line change
@@ -17,6 +17,7 @@ import Development.IDE.Plugin
1717
import Development.IDE.Core.Service
1818
import Development.IDE.Plugin.Completions.Logic
1919
import Development.IDE.Types.Location
20+
import Development.IDE.Core.IdeConfiguration
2021
import Development.IDE.Core.PositionMapping
2122
import Development.IDE.Core.RuleTypes
2223
import Development.IDE.Core.Shake
@@ -55,7 +56,7 @@ instance Binary ProduceCompletions
5556

5657
-- | Generate code actions.
5758
getCompletionsLSP
58-
:: LSP.LspFuncs ()
59+
:: LSP.LspFuncs IdeConfiguration
5960
-> IdeState
6061
-> CompletionParams
6162
-> IO (Either ResponseError CompletionResponseResult)

0 commit comments

Comments
 (0)