Close VFS when needed
[opengl.git] / src / Language / Haskell / LSP / Test.hs
index 5883271d89bc57ab997530baa57721ad47a91ca0..d3b1b65e4c5a7b9c2e9e5190897852e87a2ec018 100644 (file)
 {-# LANGUAGE OverloadedStrings #-}
+{-# LANGUAGE RankNTypes #-}
+{-# LANGUAGE ScopedTypeVariables #-}
+{-# LANGUAGE ExistentialQuantification #-}
+
+-- |
+-- Module      : Language.Haskell.LSP.Test
+-- Description : A functional testing framework for LSP servers.
+-- Maintainer  : luke_lau@icloud.com
+-- Stability   : experimental
+--
+-- A framework for testing <https://github.com/Microsoft/language-server-protocol Language Server Protocol servers> at the JSON level.
+
 module Language.Haskell.LSP.Test
   (
   -- * Sessions
-    manualSession
-  -- * Documents
-  , openDocument
-  , documentSymbols
+    runSession
+  , runSessionWithHandles
+  , runSessionWithCapabilities
+  , Session
+  -- * Sending
+  , sendRequest
+  , sendNotification
+  , sendRequest'
+  , sendNotification'
+  , sendResponse
+  -- * Receving
+  , anyRequest
+  , request
+  , anyResponse
+  , response
+  , anyNotification
+  , notification
+  , loggingNotification
+  , publishDiagnosticsNotification
+  -- * Combinators
+  , choice
+  , option
+  , optional
+  , between
+  , some
+  , many
+  , sepBy
+  , sepBy1
+  , sepEndBy1
+  , sepEndBy
+  , endBy1
+  , endBy
+  , count
+  , manyTill
+  , skipMany
+  , skipSome
+  , skipManyTill
+  , skipSomeTill
+  , (<|>)
+  , satisfy
+  -- * Utilities
+  , getInitializeResponse
+  , openDoc
+  , getDocItem
+  , documentContents
+  , getDocUri
   ) where
 
-import Control.Lens
+import Control.Applicative
+import Control.Applicative.Combinators
 import Control.Monad.IO.Class
-import Control.Monad.Trans.Reader
+import Control.Concurrent
+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.Map as Map
 import Data.Maybe
-import Data.Proxy
-import System.Process
-import qualified Language.Haskell.LSP.Client as Client
-import Language.Haskell.LSP.Messages
-import qualified Language.Haskell.LSP.TH.DataTypesJSON as LSP
-import Language.Haskell.LSP.Test.Recorded
-import Capabilities
-import Compat
-
-type Session = ReaderT Client.Client IO
-
-manualSession :: Session a -> IO ()
-manualSession f = do
-  (Just hin, Just hout, _, serverProc) <- createProcess (proc "hie" ["--lsp", "-l", "/tmp/hie.log"])
-    { std_in = CreatePipe, std_out = CreatePipe }
-  client <- Client.start $ Client.Config hin hout notificationHandler requestHandler
+import Language.Haskell.LSP.Types
+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 qualified Yi.Rope as Rope
 
+-- | Starts a new session.
+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 a
+runSessionWithCapabilities caps serverExe rootDir session = do
   pid <- getProcessID
+  absRootDir <- canonicalizePath rootDir
 
-  let initializeParams :: LSP.InitializeParams
-      initializeParams = LSP.InitializeParams (Just pid)
-                                              Nothing
-                                              Nothing
-                                              Nothing
-                                              capabilities
+  let initializeParams = InitializeParams (Just pid)
+                                          (Just $ T.pack absRootDir)
+                                          (Just $ filePathToUri absRootDir)
                                           Nothing
+                                          caps
+                                          (Just TraceOff)
 
-  Client.sendClientRequest client
-                           (Proxy :: Proxy LSP.InitializeRequest)
-                           LSP.Initialize initializeParams
-  Client.sendClientNotification client
-                                LSP.Initialized
-                                (Just LSP.InitializedParams)
+  withServer serverExe $ \serverIn serverOut _ -> runSessionWithHandles serverIn serverOut listenServer rootDir $ do
 
-  putStrLn "Session started"
+    -- Wrap the session around initialize and shutdown calls
+    sendRequest Initialize initializeParams
+    initRspMsg <- response :: Session InitializeResponse
 
-  runReaderT f client
+    liftIO $ maybe (return ()) (putStrLn . ("Error while initializing: " ++) . show ) (initRspMsg ^. LSP.error)
 
-  Client.sendClientRequest client
-                           (Proxy :: Proxy LSP.ShutdownRequest)
-                           LSP.Shutdown Nothing
-  Client.sendClientNotification client
-                                LSP.Exit
-                                (Just LSP.ExitParams)
+    initRspVar <- initRsp <$> ask
+    liftIO $ putMVar initRspVar initRspMsg
 
-  Client.stop client
+    sendNotification Initialized InitializedParams
 
-  -- todo: this interrupts the test server process as well?
-  -- interruptProcessGroupOf serverProc
-  -- waitForProcess serverProc
-  terminateProcess serverProc
+    -- Run the actual test
+    result <- session
 
-  putStrLn "Session ended"
+    sendNotification Exit ExitParams
 
-openDocument :: FilePath -> Session ()
-openDocument path = do
-  text <- liftIO $ T.readFile path
+    return result
 
-  let uri = LSP.filePathToUri path
+-- | Listens to the server output, makes sure it matches the record and
+-- signals any semaphores
+listenServer :: Handle -> Session ()
+listenServer serverOut = do
+  msgBytes <- liftIO $ getNextMessage serverOut
 
-  client <- ask
-  liftIO $ Client.sendClientNotification client LSP.TextDocumentDidOpen (Just (LSP.DidOpenTextDocumentParams (LSP.TextDocumentItem uri "haskell" 1 text)))
+  context <- ask
+  reqMap <- liftIO $ readMVar $ requestMap context
 
-documentSymbols :: FilePath -> Session (LSP.List LSP.SymbolInformation)
-documentSymbols path = do
-  let uri = LSP.filePathToUri path
+  let msg = decodeFromServerMsg reqMap msgBytes
+  liftIO $ writeChan (messageChan context) msg
 
-  client <- ask
+  listenServer serverOut
 
-  liftIO $ do
-    res <- Client.sendClientRequest client
-                                    (Proxy :: Proxy LSP.DocumentSymbolRequest)
-                                    LSP.TextDocumentDocumentSymbol (LSP.DocumentSymbolParams (LSP.TextDocumentIdentifier uri))
-    return $ case res of
-      Just (Right syms) -> syms
-      _ -> error "Failed to get document symbols"
+-- | 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
 
-notificationHandler :: Client.NotificationMessageHandler
-notificationHandler = Client.NotificationMessageHandler
-  (\(LSP.NotificationMessage _ _ (LSP.ShowMessageParams _ msg)) -> print msg)
-  (\(LSP.NotificationMessage _ _ (LSP.LogMessageParams _ msg)) -> print msg)
-  (\(LSP.NotificationMessage _ _ json) -> putStrLn $ "Telemetry: " ++ show json)
-  (\(LSP.NotificationMessage _ _ (LSP.PublishDiagnosticsParams uri diags)) ->
-    putStrLn $ "Diagnostics at " ++ showUri uri ++ ": " ++ showDiags diags)
+-- | Sends a request to the server.
+--
+-- @
+-- sendRequest (Proxy :: Proxy DocumentSymbolRequest)
+--             TextDocumentDocumentSymbol
+--             (DocumentSymbolParams docId)
+-- @
+sendRequest
+  :: (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
+  id <- curReqId <$> get
+  modify $ \c -> c { curReqId = nextId id }
 
-  where showDiags :: LSP.List LSP.Diagnostic -> String
-        showDiags (LSP.List diags) = unlines $ map (T.unpack . (^. LSP.message)) diags
-        showUri :: LSP.Uri -> String
-        showUri = fromMaybe "unknown path" . LSP.uriToFilePath
+  let req = RequestMessage' "2.0" id method params
 
+  -- Update the request map
+  reqMap <- requestMap <$> ask
+  liftIO $ modifyMVar_ reqMap $
+    \r -> return $ updateRequestMap r id method
 
+  sendMessage req
 
-requestHandler :: Client.RequestMessageHandler
-requestHandler = Client.RequestMessageHandler
-  (\m -> emptyRsp m <$ print m)
-  (\m -> emptyRsp m <$ print m)
-  (\m -> emptyRsp m <$ print m)
-  (\m -> emptyRsp m <$ print m)
-  where emptyRsp :: LSP.RequestMessage m req rsp -> LSP.ResponseMessage a
-        emptyRsp m = LSP.ResponseMessage (m ^. LSP.jsonrpc)
-                                         (lspIdToRspId $ m ^. LSP.id)
-                                         Nothing
-                                         Nothing
+  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 $
+    \r -> return $ updateRequestMap r (req ^. LSP.id) (req ^. method)
+
+  sendMessage req
+
+-- | Sends a notification to the server.
+sendNotification :: ToJSON a
+                 => ClientMethod -- ^ The notification method.
+                 -> a -- ^ The notification parameters.
+                 -> Session ()
+
+-- | 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
+
+sendResponse :: ToJSON a => ResponseMessage a -> Session ()
+sendResponse = sendMessage
+
+sendMessage :: ToJSON a => a -> Session ()
+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
+  item <- getDocItem file languageId
+  sendNotification TextDocumentDidOpen (DidOpenTextDocumentParams item)
+  TextDocumentIdentifier <$> getDocUri file
+
+-- | 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.
+           -> Session TextDocumentItem
+getDocItem file languageId = do
+  context <- ask
+  let fp = rootDir context </> file
+  contents <- liftIO $ T.readFile fp
+  return $ TextDocumentItem (filePathToUri fp) (T.pack languageId) 0 contents
+
+-- | Gets the Uri for the file corrected to the session directory.
+getDocUri :: FilePath -> Session Uri
+getDocUri file = do
+  context <- ask
+  let fp = rootDir context </> file
+  return $ filePathToUri fp
 
-        lspIdToRspId (LSP.IdInt i) = LSP.IdRspInt i
-        lspIdToRspId (LSP.IdString i) = LSP.IdRspString i