Update haskell-lsp-test

This commit is contained in:
Luke Lau 2018-07-09 13:19:55 +01:00
parent 0ae1bc5059
commit 4ff615ad0d
3 changed files with 22 additions and 21 deletions

@ -1 +1 @@
Subproject commit 3b8d5fe55d1e542587817341a797345270ca7a96
Subproject commit f8ee63f1c1d245c16f7a928c14c0e8908e6240c8

View File

@ -9,7 +9,7 @@ import Data.Aeson
import qualified Data.HashMap.Strict as H
import Data.Maybe
import Language.Haskell.LSP.Test hiding (capabilities)
import Language.Haskell.LSP.Types
import Language.Haskell.LSP.Types hiding (message)
import qualified Language.Haskell.LSP.Types as LSP (error, id)
import Test.Hspec
import System.Directory
@ -34,17 +34,17 @@ spec = do
id1 <- sendRequest' TextDocumentHover (TextDocumentPositionParams doc (Position 4 2))
skipMany anyNotification
hoverRsp <- response :: Session HoverResponse
hoverRsp <- message :: Session HoverResponse
let (Just (List contents1)) = hoverRsp ^? result . _Just . contents
liftIO $ contents1 `shouldBe` []
liftIO $ hoverRsp ^. LSP.id `shouldBe` responseId id1
id2 <- sendRequest' TextDocumentDocumentSymbol (DocumentSymbolParams doc)
symbolsRsp <- skipManyTill anyNotification response :: Session DocumentSymbolsResponse
symbolsRsp <- skipManyTill anyNotification message :: Session DocumentSymbolsResponse
liftIO $ symbolsRsp ^. LSP.id `shouldBe` responseId id2
id3 <- sendRequest' TextDocumentHover (TextDocumentPositionParams doc (Position 4 2))
hoverRsp2 <- skipManyTill anyNotification response :: Session HoverResponse
hoverRsp2 <- skipManyTill anyNotification message :: Session HoverResponse
liftIO $ hoverRsp2 ^. LSP.id `shouldBe` responseId id3
let (Just (List contents2)) = hoverRsp2 ^? result . _Just . contents
@ -131,7 +131,7 @@ spec = do
executeRsp <- sendRequest WorkspaceExecuteCommand (ExecuteCommandParams "hare:demote" (Just args))
liftIO $ executeRsp ^. result `shouldBe` Just (Object H.empty)
editReq <- request :: Session ApplyWorkspaceEditRequest
editReq <- message :: Session ApplyWorkspaceEditRequest
let expectedTextEdits = List [TextEdit (Range (Position 6 0) (Position 7 6)) " where\n bb = 5"]
liftIO $ editReq ^. params . edit `shouldBe` WorkspaceEdit
(Just $ H.singleton testUri expectedTextEdits)
@ -161,16 +161,16 @@ spec = do
-- $ runSession hieCommand "test/testdata" $ do
$ runSession hieCommandVomit "test/testdata" $ do
_doc <- openDoc "ApplyRefact2.hs" "haskell"
_diagsRspHlint <- skipManyTill anyNotification notification :: Session PublishDiagnosticsNotification
diagsRspGhc <- skipManyTill anyNotification notification :: Session PublishDiagnosticsNotification
_diagsRspHlint <- skipManyTill anyNotification message :: Session PublishDiagnosticsNotification
diagsRspGhc <- skipManyTill anyNotification message :: Session PublishDiagnosticsNotification
let (List diags) = diagsRspGhc ^. params . diagnostics
liftIO $ length diags `shouldBe` 2
_doc2 <- openDoc "HaReRename.hs" "haskell"
_diagsRspHlint2 <- skipManyTill anyNotification notification :: Session PublishDiagnosticsNotification
_diagsRspHlint2 <- skipManyTill anyNotification message :: Session PublishDiagnosticsNotification
-- errMsg <- skipManyTill anyNotification notification :: Session ShowMessageNotification
diagsRsp2 <- skipManyTill anyNotification notification :: Session PublishDiagnosticsNotification
diagsRsp2 <- skipManyTill anyNotification message :: Session PublishDiagnosticsNotification
let (List diags2) = diagsRsp2 ^. params . diagnostics
liftIO $ show diags2 `shouldBe` "[]"

View File

@ -9,7 +9,8 @@ import Data.Default
import Data.Maybe
import qualified Data.Text as T
import Language.Haskell.LSP.Test as Test
import Language.Haskell.LSP.Types as LSP hiding (contents, error)
import Language.Haskell.LSP.Types as LSP hiding (contents, error, message)
import qualified Language.Haskell.LSP.Types as LSP
import qualified Language.Haskell.LSP.Types.Capabilities as C
import Test.Hspec
import TestUtils
@ -61,8 +62,8 @@ codeActionSpec = do
doc <- openDoc "CodeActionImport.hs" "haskell"
-- ignore the first empty hlint diagnostic publish
[_,(diag:_)] <- count 2 waitForDiagnostics
liftIO $ diag ^. message `shouldBe` "Variable not in scope: when :: Bool -> IO () -> IO ()"
[_,diag:_] <- count 2 waitForDiagnostics
liftIO $ diag ^. LSP.message `shouldBe` "Variable not in scope: when :: Bool -> IO () -> IO ()"
actionsOrCommands <- getAllCodeActions doc
let actns = map fromAction actionsOrCommands
@ -89,9 +90,9 @@ codeActionSpec = do
doc <- openDoc "AddPackage.hs" "haskell"
-- ignore the first empty hlint diagnostic publish
[_,(diag:_)] <- count 2 waitForDiagnostics
[_,diag:_] <- count 2 waitForDiagnostics
liftIO $ diag ^. message `shouldSatisfy` T.isPrefixOf "Could not find module Data.Text"
liftIO $ diag ^. LSP.message `shouldSatisfy` T.isPrefixOf "Could not find module Data.Text"
(CommandOrCodeActionCodeAction action:_) <- getAllCodeActions doc
@ -108,9 +109,9 @@ codeActionSpec = do
doc <- openDoc "app/Asdf.hs" "haskell"
-- ignore the first empty hlint diagnostic publish
[_,(diag:_)] <- count 2 waitForDiagnostics
[_,diag:_] <- count 2 waitForDiagnostics
liftIO $ diag ^. message `shouldSatisfy` T.isPrefixOf "Could not find module Codec.Compression.GZip"
liftIO $ diag ^. LSP.message `shouldSatisfy` T.isPrefixOf "Could not find module Codec.Compression.GZip"
mActions <- getAllCodeActions doc
let allActions = map fromAction mActions
@ -121,7 +122,7 @@ codeActionSpec = do
forM_ allActions $ \a -> a ^. kind `shouldBe` Just CodeActionQuickFix
forM_ allActions $ \a -> a ^. command . _Just . command `shouldSatisfy` T.isSuffixOf "package:add"
executeCodeAction action
executeCodeAction action
contents <- getDocumentEdit . TextDocumentIdentifier =<< getDocUri "package.yaml"
liftIO $ do
@ -133,9 +134,9 @@ codeActionSpec = do
doc <- openDoc "src/CodeActionRedundant.hs" "haskell"
-- ignore the first empty hlint diagnostic publish
[_,(diag:_)] <- count 2 waitForDiagnostics
[_,diag:_] <- count 2 waitForDiagnostics
liftIO $ diag ^. message `shouldSatisfy` T.isPrefixOf "The import of Data.List is redundant"
liftIO $ diag ^. LSP.message `shouldSatisfy` T.isPrefixOf "The import of Data.List is redundant"
mActions <- getAllCodeActions doc
@ -158,4 +159,4 @@ codeActionSpec = do
fromAction :: CommandOrCodeAction -> CodeAction
fromAction (CommandOrCodeActionCodeAction action) = action
fromAction _ = error "Not a code action"
fromAction _ = error "Not a code action"