Log session messages, don't know why it was ever a good idea to hide them 💩
[opengl.git] / src / Language / Haskell / LSP / Test.hs
index 8da170c0d4fe6e984e2d21ffcd05dab6a79cfbc3..0e8f5bfcaa92259f253defa2d89bbb40610c1e66 100644 (file)
@@ -59,23 +59,29 @@ module Language.Haskell.LSP.Test
   , (<|>)
   , satisfy
   -- * Utilities
-  , getInitializeResponse
+  , initializeResponse
   , openDoc
-  , getDocItem
   , documentContents
+  , getDocumentEdit
   , getDocUri
+  , noDiagnostics
+  , getDocumentSymbols
+  , getDiagnostics
   ) where
 
 import Control.Applicative
 import Control.Applicative.Combinators
-import Control.Monad.IO.Class
 import Control.Concurrent
+import Control.Monad
+import Control.Monad.IO.Class
+import Control.Exception
 import Control.Lens hiding ((.=), List)
 import qualified Data.Text as T
 import qualified Data.Text.IO as T
 import Data.Aeson
 import qualified Data.ByteString.Lazy.Char8 as B
 import Data.Default
+import qualified Data.HashMap.Strict as HashMap
 import qualified Data.Map as Map
 import Data.Maybe
 import Language.Haskell.LSP.Types hiding (id, capabilities)
@@ -87,6 +93,7 @@ import Language.Haskell.LSP.Test.Exceptions
 import Language.Haskell.LSP.Test.Parsing
 import Language.Haskell.LSP.Test.Session
 import Language.Haskell.LSP.Test.Server
+import System.Console.ANSI
 import System.IO
 import System.Directory
 import System.FilePath
@@ -106,7 +113,7 @@ runSessionWithConfig :: SessionConfig -- ^ The capabilities the client should ha
                      -> Session a -- ^ The session to run.
                      -> IO a
 runSessionWithConfig config serverExe rootDir session = do
-  pid <- getProcessID
+  pid <- getCurrentProcessID
   absRootDir <- canonicalizePath rootDir
 
   let initializeParams = InitializeParams (Just pid)
@@ -115,8 +122,7 @@ runSessionWithConfig config serverExe rootDir session = do
                                           Nothing
                                           (capabilities config)
                                           (Just TraceOff)
-
-  withServer serverExe $ \serverIn serverOut _ ->
+  withServer serverExe (logStdErr config) $ \serverIn serverOut _ ->
     runSessionWithHandles serverIn serverOut listenServer config rootDir $ do
 
       -- Wrap the session around initialize and shutdown calls
@@ -158,6 +164,29 @@ documentContents doc = do
   let file = vfs Map.! (doc ^. uri)
   return $ Rope.toText $ Language.Haskell.LSP.VFS._text file
 
+-- | Parses an ApplyEditRequest, checks that it is for the passed document
+-- and returns the new content
+getDocumentEdit :: TextDocumentIdentifier -> Session T.Text
+getDocumentEdit doc = do
+  req <- request :: Session ApplyWorkspaceEditRequest
+
+  unless (checkDocumentChanges req || checkChanges req) $
+    liftIO $ throw (IncorrectApplyEditRequestException (show req))
+
+  documentContents doc
+  where
+    checkDocumentChanges :: ApplyWorkspaceEditRequest -> Bool
+    checkDocumentChanges req =
+      let changes = req ^. params . edit . documentChanges
+          maybeDocs = fmap (fmap (^. textDocument . uri)) changes
+      in case maybeDocs of
+        Just docs -> (doc ^. uri) `elem` docs
+        Nothing -> False
+    checkChanges :: ApplyWorkspaceEditRequest -> Bool
+    checkChanges req =
+      let mMap = req ^. params . edit . changes
+        in maybe False (HashMap.member (doc ^. uri)) mMap
+
 -- | Sends a request to the server.
 --
 -- @
@@ -245,13 +274,22 @@ sendResponse = sendMessage
 sendMessage :: ToJSON a => a -> Session ()
 sendMessage msg = do
   h <- serverIn <$> ask
-  liftIO $ B.hPut h $ addHeader (encode msg)
+  let encoded = encode msg
+  liftIO $ do
+
+    setSGR [SetColor Foreground Vivid Cyan]
+    putStrLn $ "--> " ++ B.unpack encoded
+    setSGR [Reset]
+
+    B.hPut h (addHeader encoded)
+
+
 
 -- | Returns the initialize response that was received from the server.
 -- The initialize requests and responses are not included the session,
 -- so if you need to test it use this.
-getInitializeResponse :: Session InitializeResponse
-getInitializeResponse = initRsp <$> ask >>= (liftIO . readMVar)
+initializeResponse :: Session InitializeResponse
+initializeResponse = initRsp <$> ask >>= (liftIO . readMVar)
 
 -- | Opens a text document and sends a notification to the client.
 openDoc :: FilePath -> String -> Session TextDocumentIdentifier
@@ -259,7 +297,7 @@ openDoc file languageId = do
   item <- getDocItem file languageId
   sendNotification TextDocumentDidOpen (DidOpenTextDocumentParams item)
   TextDocumentIdentifier <$> getDocUri file
-
+  where
   -- | Reads in a text document as the first version.
   getDocItem :: FilePath -- ^ The path to the text document to read in.
             -> String -- ^ The language ID, e.g "haskell" for .hs files.
@@ -277,3 +315,22 @@ getDocUri file = do
   let fp = rootDir context </> file
   return $ filePathToUri fp
 
+getDiagnostics :: Session [Diagnostic]
+getDiagnostics = do
+  diagsNot <- notification :: Session PublishDiagnosticsNotification
+  let (List diags) = diagsNot ^. params . LSP.diagnostics
+  return diags
+
+-- | Expects a 'PublishDiagnosticsNotification' and throws an
+-- 'UnexpectedDiagnosticsException' if there are any diagnostics
+-- returned.
+noDiagnostics :: Session ()
+noDiagnostics = do
+  diagsNot <- notification :: Session PublishDiagnosticsNotification
+  when (diagsNot ^. params . LSP.diagnostics /= List []) $ liftIO $ throw UnexpectedDiagnosticsException
+
+-- | Returns the symbols in a document.
+getDocumentSymbols :: TextDocumentIdentifier -> Session DocumentSymbolsResponse
+getDocumentSymbols doc = do
+  sendRequest TextDocumentDocumentSymbol (DocumentSymbolParams doc)
+  response
\ No newline at end of file