Add notice that this was merged into haskell/lsp
[lsp-test.git] / test / Test.hs
index 12db7851dc4c00c5e667f2d9e31d9db73d0c9c2a..344bbd587c2390b460e9212b715203fccfb2dd21 100644 (file)
@@ -1,4 +1,4 @@
-{-# LANGUAGE DataKinds #-}
+{-# LANGUAGE TypeInType #-}
 {-# LANGUAGE GADTs #-}
 {-# LANGUAGE DuplicateRecordFields #-}
 {-# LANGUAGE OverloadedStrings #-}
@@ -17,12 +17,12 @@ import           Control.Concurrent
 import           Control.Monad.IO.Class
 import           Control.Monad
 import           Control.Lens hiding (List)
-import           Language.Haskell.LSP.Test
-import           Language.Haskell.LSP.Types
-import           Language.Haskell.LSP.Types.Lens hiding
+import           Language.LSP.Test
+import           Language.LSP.Types
+import           Language.LSP.Types.Lens hiding
   (capabilities, message, rename, applyEdit)
-import qualified Language.Haskell.LSP.Types.Lens as LSP
-import           Language.Haskell.LSP.Types.Capabilities as LSP
+import qualified Language.LSP.Types.Lens as LSP
+import           Language.LSP.Types.Capabilities as LSP
 import           System.Directory
 import           System.FilePath
 import           System.Timeout
@@ -53,7 +53,7 @@ main = findServer >>= \serverExe -> hspec $ do
                     -- won't receive a request - will timeout
                     -- incoming logging requests shouldn't increase the
                     -- timeout
-                    withTimeout 5 $ skipManyTill anyMessage (message SWorkspaceApplyEdit) :: Session ApplyWorkspaceEditRequest
+                    withTimeout 5 $ skipManyTill anyMessage (message SWorkspaceApplyEdit)
           -- wait just a bit longer than 5 seconds so we have time
           -- to open the document
           in timeout 6000000 sesh `shouldThrow` anySessionException
@@ -118,7 +118,7 @@ main = findServer >>= \serverExe -> hspec $ do
               selector _ = False
             in runSession serverExe fullCaps "test/data/renamePass" publishDiagnosticsNotification `shouldThrow` selector
         it "provides the correct types that were expected and received" $
-          let selector (UnexpectedMessage "STextDocumentRename" (FromServerRsp STextDocumentDocumentSymbol _)) = True
+          let selector (UnexpectedMessage "Response for: STextDocumentRename" (FromServerRsp STextDocumentDocumentSymbol _)) = True
               selector _ = False
               sesh = do
                 doc <- openDoc "Desktop/simple.hs" "haskell"
@@ -161,8 +161,10 @@ main = findServer >>= \serverExe -> hspec $ do
     it "works" $ runSession serverExe fullCaps "test/data/refactor" $ do
       doc <- openDoc "Main.hs" "haskell"
       waitForDiagnostics
-      [InR action] <- getCodeActions doc (Range (Position 1 14) (Position 1 18))
+      [InR action] <- getCodeActions doc (Range (Position 0 0) (Position 0 2))
+      actions <- getCodeActions doc (Range (Position 1 14) (Position 1 18))
       liftIO $ action ^. title `shouldBe` "Delete this"
+      liftIO $ actions `shouldSatisfy` null
 
   describe "getAllCodeActions" $
     it "works" $ runSession serverExe fullCaps "test/data/refactor" $ do