X-Git-Url: http://git.lukelau.me/?a=blobdiff_plain;f=src%2FLanguage%2FHaskell%2FLSP%2FTest%2FSession.hs;h=0553160aee215862ebb4fbad547f087a9fcbaca6;hb=3581d880c87b59cc4c856aee83f77fea9a38890b;hp=6599cbdef746b1aa659b7ea92ab6665639654e28;hpb=22df37c703e39fa5ebeb130be5785b3a9713c520;p=opengl.git diff --git a/src/Language/Haskell/LSP/Test/Session.hs b/src/Language/Haskell/LSP/Test/Session.hs index 6599cbd..0553160 100644 --- a/src/Language/Haskell/LSP/Test/Session.hs +++ b/src/Language/Haskell/LSP/Test/Session.hs @@ -11,6 +11,7 @@ module Language.Haskell.LSP.Test.Session , get , put , modify + , modifyM , ask) where @@ -32,11 +33,14 @@ import Data.Conduit.Parser import Data.Default import Data.Foldable import Data.List +import qualified Data.Map as Map import qualified Data.Text as T +import qualified Data.Text.IO as T import qualified Data.HashMap.Strict as HashMap +import Data.Maybe import Language.Haskell.LSP.Messages import Language.Haskell.LSP.TH.ClientCapabilities -import Language.Haskell.LSP.Types +import Language.Haskell.LSP.Types hiding (error) import Language.Haskell.LSP.VFS import Language.Haskell.LSP.Test.Compat import Language.Haskell.LSP.Test.Decoding @@ -62,10 +66,11 @@ data SessionConfig = SessionConfig { capabilities :: ClientCapabilities -- ^ Specific capabilities the client should advertise. Default is yes to everything. , timeout :: Int -- ^ Maximum time to wait for a request in seconds. Defaults to 60. + , logStdErr :: Bool -- ^ When True redirects the servers stderr output to haskell-lsp-test's stdout. Defaults to False } instance Default SessionConfig where - def = SessionConfig def 60 + def = SessionConfig def 60 False class Monad m => MonadSessionConfig m where sessionConfig :: m SessionConfig @@ -127,6 +132,12 @@ put = lift . State.put modify :: Monad m => (s -> s) -> ParserStateReader a s r m () modify = lift . State.modify +modifyM :: Monad m => (s -> m s) -> ParserStateReader a s r m () +modifyM f = do + old <- lift State.get + new <- lift $ lift $ lift $ f old + lift $ State.put new + ask :: Monad m => ParserStateReader a s r m r ask = lift $ lift Reader.ask @@ -168,30 +179,57 @@ runSessionWithHandles serverIn serverOut serverHandler config rootDir session = processTextChanges :: FromServerMessage -> SessionProcessor () processTextChanges (ReqApplyWorkspaceEdit r) = do - List changeParams <- case r ^. params . edit . documentChanges of - Just cs -> mapM applyTextDocumentEdit cs + + allChangeParams <- case r ^. params . edit . documentChanges of + Just (List cs) -> do + mapM_ (checkIfNeedsOpened . (^. textDocument . uri)) cs + return $ map getParams cs Nothing -> case r ^. params . edit . changes of - Just cs -> mapM (uncurry applyTextEdit) (List (HashMap.toList cs)) - Nothing -> return (List []) + Just cs -> do + mapM_ checkIfNeedsOpened (HashMap.keys cs) + return $ concatMap (uncurry getChangeParams) (HashMap.toList cs) + Nothing -> error "No changes!" - let groupedParams = groupBy (\a b -> (a ^. textDocument == b ^. textDocument)) changeParams + oldVFS <- vfs <$> lift State.get + newVFS <- liftIO $ changeFromServerVFS oldVFS r + lift $ State.modify (\s -> s { vfs = newVFS }) + + let groupedParams = groupBy (\a b -> (a ^. textDocument == b ^. textDocument)) allChangeParams mergedParams = map mergeParams groupedParams + ctx <- lift $ lift Reader.ask + -- TODO: Don't do this when replaying a session forM_ mergedParams $ \p -> do - h <- serverIn <$> lift (lift Reader.ask) - let msg = NotificationMessage "2.0" TextDocumentDidChange p + let h = serverIn ctx + msg = NotificationMessage "2.0" TextDocumentDidChange p liftIO $ B.hPut h $ addHeader (encode msg) - where applyTextDocumentEdit (TextDocumentEdit docId (List edits)) = do + where checkIfNeedsOpened uri = do oldVFS <- vfs <$> lift State.get - let changeEvents = map (\e -> TextDocumentContentChangeEvent (Just (e ^. range)) Nothing (e ^. newText)) edits - params = DidChangeTextDocumentParams docId (List changeEvents) - newVFS <- liftIO $ changeVFS oldVFS (fmClientDidChangeTextDocumentNotification params) + ctx <- lift $ lift Reader.ask + + -- if its not open, open it + unless (uri `Map.member` oldVFS) $ do + let fp = fromJust $ uriToFilePath uri + contents <- liftIO $ T.readFile fp + let item = TextDocumentItem (filePathToUri fp) "" 0 contents + msg = NotificationMessage "2.0" TextDocumentDidOpen (DidOpenTextDocumentParams item) + liftIO $ B.hPut (serverIn ctx) $ addHeader (encode msg) + + oldVFS <- vfs <$> lift State.get + newVFS <- liftIO $ openVFS oldVFS msg lift $ State.modify (\s -> s { vfs = newVFS }) - return params - applyTextEdit uri edits = applyTextDocumentEdit (TextDocumentEdit (VersionedTextDocumentIdentifier uri 0) edits) + getParams (TextDocumentEdit docId (List edits)) = + let changeEvents = map (\e -> TextDocumentContentChangeEvent (Just (e ^. range)) Nothing (e ^. newText)) edits + in DidChangeTextDocumentParams docId (List changeEvents) + + textDocumentVersions uri = map (VersionedTextDocumentIdentifier uri) [0..] + + textDocumentEdits uri edits = map (\(v, e) -> TextDocumentEdit v (List [e])) $ zip (textDocumentVersions uri) edits + + getChangeParams uri (List edits) = map getParams (textDocumentEdits uri (reverse edits)) mergeParams :: [DidChangeTextDocumentParams] -> DidChangeTextDocumentParams mergeParams params = let events = concat (toList (map (toList . (^. contentChanges)) params))