Close VFS when needed
[opengl.git] / src / Language / Haskell / LSP / Test.hs
index 087143fa8960537db6d71dab2c3bc70e82e83221..d3b1b65e4c5a7b9c2e9e5190897852e87a2ec018 100644 (file)
@@ -15,7 +15,8 @@ module Language.Haskell.LSP.Test
   (
   -- * Sessions
     runSession
-  , runSessionWithHandler
+  , runSessionWithHandles
+  , runSessionWithCapabilities
   , Session
   -- * Sending
   , sendRequest
@@ -24,8 +25,11 @@ module Language.Haskell.LSP.Test
   , sendNotification'
   , sendResponse
   -- * Receving
+  , anyRequest
   , request
+  , anyResponse
   , response
+  , anyNotification
   , notification
   , loggingNotification
   , publishDiagnosticsNotification
@@ -51,40 +55,53 @@ module Language.Haskell.LSP.Test
   , (<|>)
   , satisfy
   -- * Utilities
+  , getInitializeResponse
   , openDoc
   , getDocItem
+  , documentContents
   , getDocUri
   ) where
 
 import Control.Applicative
 import Control.Applicative.Combinators
-import Control.Monad
 import Control.Monad.IO.Class
 import Control.Concurrent
-import Control.Lens
+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 Data.Proxy
-import System.Process
+import qualified Data.Map as Map
+import Data.Maybe
 import Language.Haskell.LSP.Types
-import qualified  Language.Haskell.LSP.Types as LSP (error)
-import Language.Haskell.LSP.Messages
+import qualified  Language.Haskell.LSP.Types as LSP (error, id)
+import Language.Haskell.LSP.TH.ClientCapabilities
+import Language.Haskell.LSP.VFS
 import Language.Haskell.LSP.Test.Compat
+import Language.Haskell.LSP.Test.Decoding
+import Language.Haskell.LSP.Test.Parsing
+import Language.Haskell.LSP.Test.Session
+import Language.Haskell.LSP.Test.Server
 import System.IO
 import System.Directory
 import System.FilePath
-import Language.Haskell.LSP.Test.Decoding
-import Language.Haskell.LSP.Test.Parsing
+import qualified Yi.Rope as Rope
 
 -- | Starts a new session.
-runSession :: FilePath -- ^ The filepath to the server executable.
+runSession :: String -- ^ The command to run the server.
+           -> FilePath -- ^ The filepath to the root directory for the session.
+           -> Session a -- ^ The session to run.
+           -> IO a
+runSession = runSessionWithCapabilities def
+
+-- | Starts a new sesion with a client with the specified capabilities.
+runSessionWithCapabilities :: ClientCapabilities -- ^ The capabilities the client should have.
+                           -> String -- ^ The command to run the server.
                            -> FilePath -- ^ The filepath to the root directory for the session.
                            -> Session a -- ^ The session to run.
-           -> IO ()
-runSession serverExe rootDir session = do
+                           -> IO a
+runSessionWithCapabilities caps serverExe rootDir session = do
   pid <- getProcessID
   absRootDir <- canonicalizePath rootDir
 
@@ -92,52 +109,27 @@ runSession serverExe rootDir session = do
                                           (Just $ T.pack absRootDir)
                                           (Just $ filePathToUri absRootDir)
                                           Nothing
-                                          def
+                                          caps
                                           (Just TraceOff)
 
-  runSessionWithHandler listenServer serverExe rootDir $ do
+  withServer serverExe $ \serverIn serverOut _ -> runSessionWithHandles serverIn serverOut listenServer rootDir $ do
 
     -- Wrap the session around initialize and shutdown calls
-    sendRequest (Proxy :: Proxy InitializeRequest) Initialize initializeParams
-    RspInitialize initRsp <- response
-    liftIO $ maybe (return ()) (putStrLn . ("Error while initializing: " ++) . show ) (initRsp ^. LSP.error)
+    sendRequest Initialize initializeParams
+    initRspMsg <- response :: Session InitializeResponse
+
+    liftIO $ maybe (return ()) (putStrLn . ("Error while initializing: " ++) . show ) (initRspMsg ^. LSP.error)
+
+    initRspVar <- initRsp <$> ask
+    liftIO $ putMVar initRspVar initRspMsg
 
     sendNotification Initialized InitializedParams
 
     -- Run the actual test
-    session
+    result <- session
 
     sendNotification Exit ExitParams
 
--- | An internal version of 'runSession' that allows for a custom handler to listen to the server.
--- It also does not automatically send initialize and exit messages.
-runSessionWithHandler :: (Handle -> Session ())
-                      -> FilePath
-                      -> FilePath
-                      -> Session a
-                      -> IO a
-runSessionWithHandler serverHandler serverExe rootDir session = do
-  absRootDir <- canonicalizePath rootDir
-
-  (Just serverIn, Just serverOut, Nothing, serverProc) <- createProcess
-    (proc serverExe ["--lsp", "-d", "-l", "/tmp/hie-test.log"])
-    { std_in = CreatePipe, std_out = CreatePipe }
-
-  hSetBuffering serverIn  NoBuffering
-  hSetBuffering serverOut NoBuffering
-
-  reqMap <- newMVar newRequestMap
-  messageChan <- newChan
-  meaninglessChan <- newChan
-
-  let context = SessionContext serverIn absRootDir messageChan reqMap
-      initState = SessionState (IdInt 9)
-
-  forkIO $ void $ runSession' meaninglessChan context initState (serverHandler serverOut)
-  (result, _) <- runSession' messageChan context initState session
-
-  terminateProcess serverProc
-
     return result
 
 -- | Listens to the server output, makes sure it matches the record and
@@ -149,10 +141,18 @@ listenServer serverOut = do
   context <- ask
   reqMap <- liftIO $ readMVar $ requestMap context
 
-  liftIO $ writeChan (messageChan context) $ decodeFromServerMsg reqMap msgBytes
+  let msg = decodeFromServerMsg reqMap msgBytes
+  liftIO $ writeChan (messageChan context) msg
 
   listenServer serverOut
 
+-- | The current text contents of a document.
+documentContents :: TextDocumentIdentifier -> Session T.Text
+documentContents doc = do
+  vfs <- vfs <$> get
+  let file = vfs Map.! (doc ^. uri)
+  return $ Rope.toText $ Language.Haskell.LSP.VFS._text file
+
 -- | Sends a request to the server.
 --
 -- @
@@ -161,29 +161,45 @@ listenServer serverOut = do
 --             (DocumentSymbolParams docId)
 -- @
 sendRequest
-  :: forall params resp. (ToJSON params, ToJSON resp, FromJSON resp)
-  => Proxy (RequestMessage ClientMethod params resp) -- ^ A proxy to provide more type information about the request.
-  -> ClientMethod -- ^ The request method.
+  :: (ToJSON params)
+  => --Proxy (RequestMessage ClientMethod params resp) -- ^ A proxy to provide more type information about the request.
+  ClientMethod -- ^ The request method.
   -> params -- ^ The request parameters.
   -> Session LspId -- ^ The id of the request that was sent.
-sendRequest method params = do
+sendRequest method params = do
   id <- curReqId <$> get
   modify $ \c -> c { curReqId = nextId id }
 
-  let req = RequestMessage "2.0" id method params :: RequestMessage ClientMethod params resp
+  let req = RequestMessage' "2.0" id method params
 
-  sendRequest' req
+  -- Update the request map
+  reqMap <- requestMap <$> ask
+  liftIO $ modifyMVar_ reqMap $
+    \r -> return $ updateRequestMap r id method
+
+  sendMessage req
 
   return id
 
   where nextId (IdInt i) = IdInt (i + 1)
         nextId (IdString s) = IdString $ T.pack $ show $ read (T.unpack s) + 1
 
+-- | A custom type for request message that doesn't
+-- need a response type, allows us to infer the request
+-- message type without using proxies.
+data RequestMessage' a = RequestMessage' T.Text LspId ClientMethod a
+
+instance ToJSON a => ToJSON (RequestMessage' a) where
+  toJSON (RequestMessage' rpc id method params) =
+    object ["jsonrpc" .= rpc, "id" .= id, "method" .= method, "params" .= params]
+
+
 sendRequest' :: (ToJSON a, ToJSON b) => RequestMessage ClientMethod a b -> Session ()
 sendRequest' req = do
   -- Update the request map
   reqMap <- requestMap <$> ask
-  liftIO $ modifyMVar_ reqMap (return . flip updateRequestMap req)
+  liftIO $ modifyMVar_ reqMap $
+    \r -> return $ updateRequestMap r (req ^. LSP.id) (req ^. method)
 
   sendMessage req
 
@@ -192,9 +208,28 @@ sendNotification :: ToJSON a
                  => ClientMethod -- ^ The notification method.
                  -> a -- ^ The notification parameters.
                  -> Session ()
-sendNotification method params =
-  let notif = NotificationMessage "2.0" method params
-    in sendNotification' notif
+
+-- | Open a virtual file if we send a did open text document notification
+sendNotification TextDocumentDidOpen params = do
+  let params' = fromJust $ decode $ encode params
+      n :: DidOpenTextDocumentNotification
+      n = NotificationMessage "2.0" TextDocumentDidOpen params'
+  oldVFS <- vfs <$> get
+  newVFS <- liftIO $ openVFS oldVFS n
+  modify (\s -> s { vfs = newVFS })
+  sendNotification' n
+
+-- | Close a virtual file if we send a close text document notification
+sendNotification TextDocumentDidClose params = do
+  let params' = fromJust $ decode $ encode params
+      n :: DidCloseTextDocumentNotification
+      n = NotificationMessage "2.0" TextDocumentDidClose params'
+  oldVFS <- vfs <$> get
+  newVFS <- liftIO $ closeVFS oldVFS n
+  modify (\s -> s { vfs = newVFS })
+  sendNotification' n
+
+sendNotification method params = sendNotification' (NotificationMessage "2.0" method params)
 
 sendNotification' :: (ToJSON a, ToJSON b) => NotificationMessage a b -> Session ()
 sendNotification' = sendMessage
@@ -207,6 +242,12 @@ sendMessage msg = do
   h <- serverIn <$> ask
   liftIO $ B.hPut h $ addHeader (encode msg)
 
+-- | 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)
+
 -- | Opens a text document and sends a notification to the client.
 openDoc :: FilePath -> String -> Session TextDocumentIdentifier
 openDoc file languageId = do
@@ -230,3 +271,4 @@ getDocUri file = do
   context <- ask
   let fp = rootDir context </> file
   return $ filePathToUri fp
+