Integrate Parsec transformer into Session monad
authorLuke Lau <luke_lau@icloud.com>
Thu, 7 Jun 2018 17:06:08 +0000 (13:06 -0400)
committerLuke Lau <luke_lau@icloud.com>
Thu, 7 Jun 2018 17:06:08 +0000 (13:06 -0400)
example/Main.hs
haskell-lsp-test.cabal
src/Language/Haskell/LSP/Test.hs
src/Language/Haskell/LSP/Test/Decoding.hs
src/Language/Haskell/LSP/Test/Parsing.hs
test/Test.hs

index 5aaa2d13abee6adb516dcfece381e3cd215d1e50..d66e17e11075f0f018e7ee8a37eaf4410734212a 100644 (file)
@@ -13,5 +13,6 @@ main = runSession "test/recordings/renamePass" $ do
   
   sendRequest (Proxy :: Proxy DocumentSymbolRequest) TextDocumentDocumentSymbol (DocumentSymbolParams docId)
 
-  syms <- getMessage :: Session DocumentSymbolsResponse
-  liftIO $ print syms
\ No newline at end of file
+  skipMany loggingNotification
+
+  response >>= liftIO . print
\ No newline at end of file
index af514783d604b8483844f1b0fd7c70b96481dbbd..7dcbc716ea6338680fb39e1f79c63af24f8c16e7 100644 (file)
@@ -54,7 +54,7 @@ test-suite tests
                      , lens
                      , directory
                      , haskell-lsp-test
-                     , haskell-lsp-types
+                     , haskell-lsp
   default-language:    Haskell2010
 
 executable example
index 5c59417b48d36acce11e51eab9b3596392f8173f..495714c02e6bd3c28d09b0fd97eff1a7b7e766a3 100644 (file)
@@ -16,6 +16,17 @@ module Language.Haskell.LSP.Test
   -- * Sessions
     runSession
   , runSessionWithHandler
+  -- | A session representing one instance of launching and connecting to a server.
+  -- 
+  -- You can send and receive messages to the server within 'Session' via 'getMessage',
+  -- 'sendRequest' and 'sendNotification'.
+  --
+  -- @
+  -- runSession \"path\/to\/root\/dir\" $ do
+  --   docItem <- getDocItem "Desktop/simple.hs" "haskell"
+  --   sendNotification TextDocumentDidOpen (DidOpenTextDocumentParams docItem)
+  --   diagnostics <- getMessage :: Session PublishDiagnosticsNotification
+  -- @
   , Session
   -- * Sending
   , sendRequest
@@ -24,7 +35,13 @@ module Language.Haskell.LSP.Test
   , sendNotification'
   , sendResponse'
   -- * Receving
-  , getMessage
+  , request
+  , response
+  , notification
+  , loggingNotification
+  -- * Parsing
+  , many
+  , skipMany
   -- * Utilities
   , getDocItem
   , getDocUri
@@ -34,48 +51,23 @@ import Control.Monad
 import Control.Monad.Trans.Class
 import Control.Monad.IO.Class
 import Control.Monad.Trans.Reader
-import Control.Monad.Trans.State
 import Control.Concurrent
 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.Maybe
 import Data.Proxy
 import System.Process
 import Language.Haskell.LSP.Types hiding (error, id)
+import Language.Haskell.LSP.Messages
 import Language.Haskell.LSP.Test.Compat
 import System.IO
 import System.Directory
 import System.FilePath
 import Language.Haskell.LSP.Test.Decoding
-
-data SessionContext = SessionContext
-  {
-    messageSema :: MVar B.ByteString,
-    serverIn :: Handle,
-    rootDir :: FilePath
-  }
-
-newtype SessionState = SessionState
-  {
-    curReqId :: LspId
-  }
-
--- | A session representing one instance of launching and connecting to a server.
--- 
--- You can send and receive messages to the server within 'Session' via 'getMessage',
--- 'sendRequest' and 'sendNotification'.
---
--- @
--- runSession \"path\/to\/root\/dir\" $ do
---   docItem <- getDocItem "Desktop/simple.hs" "haskell"
---   sendNotification TextDocumentDidOpen (DidOpenTextDocumentParams docItem)
---   diagnostics <- getMessage :: Session PublishDiagnosticsNotification
--- @
--- 
-type Session = StateT SessionState (ReaderT SessionContext IO)
+import Language.Haskell.LSP.Test.Parsing
+import Text.Parsec
 
 -- | Starts a new session.
 runSession :: FilePath -- ^ The filepath to the root directory for the session.
@@ -96,8 +88,9 @@ runSession rootDir session = do
 
     -- Wrap the session around initialize and shutdown calls
     sendRequest (Proxy :: Proxy InitializeRequest) Initialize initializeParams
-    (ResponseMessage _ _ (Just (InitializeResponseCapabilities _)) e) <- getMessage
-    liftIO $ maybe (return ()) (putStrLn . ("Error when initializing: " ++) . show ) e
+    -- (ResponseMessage _ _ (Just (InitializeResponseCapabilities _)) e) <- getMessage
+    -- liftIO $ maybe (return ()) (putStrLn . ("Error when initializing: " ++) . show ) e
+    (RspInitialize _ ) <- response
 
     sendNotification Initialized InitializedParams
 
@@ -120,32 +113,32 @@ runSessionWithHandler serverHandler rootDir session = do
   hSetBuffering serverIn  NoBuffering
   hSetBuffering serverOut NoBuffering
 
-  messageSema <- newEmptyMVar
+  reqMap <- newMVar newRequestMap
+  messageChan <- newChan
+  meaninglessChan <- newChan
 
-  let context = SessionContext messageSema serverIn absRootDir
+  let context = SessionContext serverIn absRootDir messageChan reqMap
       initState = SessionState (IdInt 9)
 
-  forkIO $ void $ runReaderT (runStateT (serverHandler serverOut) initState) context
-  (result, _) <- runReaderT (runStateT session initState) context
+  forkIO $ void $ runReaderT (runParserT (serverHandler serverOut) initState "" meaninglessChan) context
+  result <- runReaderT (runParserT session initState "" messageChan) context
 
   terminateProcess serverProc
 
-  return result
+  case result of
+    Right x -> return x
+    Left err -> error $ show err
 
 -- | Listens to the server output, makes sure it matches the record and
 -- signals any semaphores
 listenServer :: Handle -> Session ()
 listenServer serverOut = do
-  context <- lift ask
   msgBytes <- liftIO $ getNextMessage serverOut
 
-  liftIO $ case decode msgBytes :: Maybe LogMessageNotification of
-    -- Just print log and show messages
-    Just (NotificationMessage _ WindowLogMessage (LogMessageParams _ msg)) -> T.putStrLn msg
-    _ -> case decode msgBytes :: Maybe ShowMessageNotification of
-      Just (NotificationMessage _ WindowShowMessage (ShowMessageParams _ msg)) -> T.putStrLn msg
-    -- Give everything else for getMessage to handle
-      _ -> putMVar (messageSema context) msgBytes
+  context <- lift ask
+  reqMap <- liftIO $ readMVar $ requestMap context
+
+  liftIO $ writeChan (messageChan context) $ decodeFromServerMsg reqMap msgBytes
 
   listenServer serverOut
 
@@ -163,8 +156,8 @@ sendRequest
   -> params -- ^ The request parameters.
   -> Session LspId -- ^ The id of the request that was sent.
 sendRequest _ method params = do
-  id <- curReqId <$> get
-  get >>= \c -> put c { curReqId = nextId id }
+  id <- curReqId <$> getState
+  modifyState $ \c -> c { curReqId = nextId id }
 
   let req = RequestMessage "2.0" id method params :: RequestMessage ClientMethod params resp
 
@@ -175,8 +168,13 @@ sendRequest _ method params = do
   where nextId (IdInt i) = IdInt (i + 1)
         nextId (IdString s) = IdString $ T.pack $ show $ read (T.unpack s) + 1
 
-sendRequest' :: (ToJSON a, ToJSON b, ToJSON c) => RequestMessage a b c -> Session ()
-sendRequest' = sendMessage
+sendRequest' :: (ToJSON a, ToJSON b) => RequestMessage ClientMethod a b -> Session ()
+sendRequest' req = do
+  -- Update the request map
+  reqMap <- requestMap <$> lift ask
+  liftIO $ modifyMVar_ reqMap (return . flip updateRequestMap req)
+
+  sendMessage req
 
 -- | Sends a notification to the server.
 sendNotification :: ToJSON a
@@ -198,13 +196,6 @@ sendMessage msg = do
   h <- serverIn <$> lift ask
   liftIO $ B.hPut h $ addHeader (encode msg)
 
--- | Reads in a message from the server.
-getMessage :: FromJSON a => Session a
-getMessage = do
-  sema <- messageSema <$> lift ask
-  bytes <- liftIO $ takeMVar sema
-  return $ fromMaybe (error $ "Wrong type! Got: " ++ show bytes) (decode bytes)
-
 -- | 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.
index 4e871155aff4dece1318d6b25c1b851b6ecca0c5..f71a52fe9620641a87cae74bfdbd8686d1346e13 100644 (file)
@@ -46,64 +46,67 @@ getHeaders h = do
   let (name, val) = span (/= ':') l
   if null val then return [] else ((name, drop 2 val) :) <$> getHeaders h
 
-type RequestMap = HM.HashMap LspId FromClientMessage
+type RequestMap = HM.HashMap LspId ClientMethod
+
+newRequestMap :: RequestMap
+newRequestMap = HM.empty
+
+updateRequestMap :: RequestMap -> RequestMessage ClientMethod a b -> RequestMap
+updateRequestMap reqMap msg = HM.insert (msg ^. id) (msg ^. method) reqMap
 
 getRequestMap :: [FromClientMessage] -> RequestMap
 getRequestMap = foldl helper HM.empty
  where
   helper acc msg = case msg of
-    (ReqInitialize val) -> insert val msg acc
-    (ReqShutdown val) -> insert val msg acc
-    (ReqHover val) -> insert val msg acc
-    (ReqCompletion val) -> insert val msg acc
-    (ReqCompletionItemResolve val) -> insert val msg acc
-    (ReqSignatureHelp val) -> insert val msg acc
-    (ReqDefinition val) -> insert val msg acc
-    (ReqFindReferences val) -> insert val msg acc
-    (ReqDocumentHighlights val) -> insert val msg acc
-    (ReqDocumentSymbols val) -> insert val msg acc
-    (ReqWorkspaceSymbols val) -> insert val msg acc
-    (ReqCodeAction val) -> insert val msg acc
-    (ReqCodeLens val) -> insert val msg acc
-    (ReqCodeLensResolve val) -> insert val msg acc
-    (ReqDocumentFormatting val) -> insert val msg acc
-    (ReqDocumentRangeFormatting val) -> insert val msg acc
-    (ReqDocumentOnTypeFormatting val) -> insert val msg acc
-    (ReqRename val) -> insert val msg acc
-    (ReqExecuteCommand val) -> insert val msg acc
-    (ReqDocumentLink val) -> insert val msg acc
-    (ReqDocumentLinkResolve val) -> insert val msg acc
-    (ReqWillSaveWaitUntil val) -> insert val msg acc
+    (ReqInitialize val) -> insert val acc
+    (ReqShutdown val) -> insert val acc
+    (ReqHover val) -> insert val acc
+    (ReqCompletion val) -> insert val acc
+    (ReqCompletionItemResolve val) -> insert val acc
+    (ReqSignatureHelp val) -> insert val acc
+    (ReqDefinition val) -> insert val acc
+    (ReqFindReferences val) -> insert val acc
+    (ReqDocumentHighlights val) -> insert val acc
+    (ReqDocumentSymbols val) -> insert val acc
+    (ReqWorkspaceSymbols val) -> insert val acc
+    (ReqCodeAction val) -> insert val acc
+    (ReqCodeLens val) -> insert val acc
+    (ReqCodeLensResolve val) -> insert val acc
+    (ReqDocumentFormatting val) -> insert val acc
+    (ReqDocumentRangeFormatting val) -> insert val acc
+    (ReqDocumentOnTypeFormatting val) -> insert val acc
+    (ReqRename val) -> insert val acc
+    (ReqExecuteCommand val) -> insert val acc
+    (ReqDocumentLink val) -> insert val acc
+    (ReqDocumentLinkResolve val) -> insert val acc
+    (ReqWillSaveWaitUntil val) -> insert val acc
     _ -> acc
-  insert m = HM.insert (m ^. id)
+  insert m = HM.insert (m ^. id) (m ^. method)
 
-matchResponseMsgType :: FromClientMessage -> B.ByteString -> FromServerMessage
+matchResponseMsgType :: ClientMethod -> B.ByteString -> FromServerMessage
 matchResponseMsgType req bytes = case req of
-  ReqInitialize _ -> RspInitialize $ fromJust $ decode bytes
-  ReqShutdown   _ -> RspShutdown $ fromJust $ decode bytes
-  ReqHover      _ -> RspHover $ fromJust $ decode bytes
-  ReqCompletion _ -> RspCompletion $ fromJust $ decode bytes
-  ReqCompletionItemResolve _ ->
-    RspCompletionItemResolve $ fromJust $ decode bytes
-  ReqSignatureHelp      _ -> RspSignatureHelp $ fromJust $ decode bytes
-  ReqDefinition         _ -> RspDefinition $ fromJust $ decode bytes
-  ReqFindReferences     _ -> RspFindReferences $ fromJust $ decode bytes
-  ReqDocumentHighlights _ -> RspDocumentHighlights $ fromJust $ decode bytes
-  ReqDocumentSymbols    _ -> RspDocumentSymbols $ fromJust $ decode bytes
-  ReqWorkspaceSymbols   _ -> RspWorkspaceSymbols $ fromJust $ decode bytes
-  ReqCodeAction         _ -> RspCodeAction $ fromJust $ decode bytes
-  ReqCodeLens           _ -> RspCodeLens $ fromJust $ decode bytes
-  ReqCodeLensResolve    _ -> RspCodeLensResolve $ fromJust $ decode bytes
-  ReqDocumentFormatting _ -> RspDocumentFormatting $ fromJust $ decode bytes
-  ReqDocumentRangeFormatting _ ->
-    RspDocumentRangeFormatting $ fromJust $ decode bytes
-  ReqDocumentOnTypeFormatting _ ->
-    RspDocumentOnTypeFormatting $ fromJust $ decode bytes
-  ReqRename              _ -> RspRename $ fromJust $ decode bytes
-  ReqExecuteCommand      _ -> RspExecuteCommand $ fromJust $ decode bytes
-  ReqDocumentLink        _ -> RspDocumentLink $ fromJust $ decode bytes
-  ReqDocumentLinkResolve _ -> RspDocumentLinkResolve $ fromJust $ decode bytes
-  ReqWillSaveWaitUntil   _ -> RspWillSaveWaitUntil $ fromJust $ decode bytes
+  Initialize                    -> RspInitialize $ fromJust $ decode bytes
+  Shutdown                      -> RspShutdown $ fromJust $ decode bytes
+  TextDocumentHover             -> RspHover $ fromJust $ decode bytes
+  TextDocumentCompletion        -> RspCompletion $ fromJust $ decode bytes
+  CompletionItemResolve         -> RspCompletionItemResolve $ fromJust $ decode bytes
+  TextDocumentSignatureHelp     -> RspSignatureHelp $ fromJust $ decode bytes
+  TextDocumentDefinition        -> RspDefinition $ fromJust $ decode bytes
+  TextDocumentReferences        -> RspFindReferences $ fromJust $ decode bytes
+  TextDocumentDocumentHighlight -> RspDocumentHighlights $ fromJust $ decode bytes
+  TextDocumentDocumentSymbol    -> RspDocumentSymbols $ fromJust $ decode bytes
+  WorkspaceSymbol               -> RspWorkspaceSymbols $ fromJust $ decode bytes
+  TextDocumentCodeAction        -> RspCodeAction $ fromJust $ decode bytes
+  TextDocumentCodeLens          -> RspCodeLens $ fromJust $ decode bytes
+  CodeLensResolve               -> RspCodeLensResolve $ fromJust $ decode bytes
+  TextDocumentFormatting        -> RspDocumentFormatting $ fromJust $ decode bytes
+  TextDocumentRangeFormatting   -> RspDocumentRangeFormatting $ fromJust $ decode bytes
+  TextDocumentOnTypeFormatting  -> RspDocumentOnTypeFormatting $ fromJust $ decode bytes
+  TextDocumentRename            -> RspRename $ fromJust $ decode bytes
+  WorkspaceExecuteCommand       -> RspExecuteCommand $ fromJust $ decode bytes
+  TextDocumentDocumentLink      -> RspDocumentLink $ fromJust $ decode bytes
+  DocumentLinkResolve           -> RspDocumentLinkResolve $ fromJust $ decode bytes
+  TextDocumentWillSaveWaitUntil -> RspWillSaveWaitUntil $ fromJust $ decode bytes
   x                             -> error $ "Not a request: " ++ show x
 
 decodeFromServerMsg :: RequestMap -> B.ByteString -> FromServerMessage
index 9d2dd702c78d2065b53835e12cc11a4f3dd4b9be..b5f5b6b4a740a3d17642cd185293f3877ad469a3 100644 (file)
@@ -3,26 +3,51 @@
 {-# LANGUAGE FlexibleInstances #-}
 module Language.Haskell.LSP.Test.Parsing where
 
+import Control.Monad.IO.Class
+import Control.Monad.Trans.Reader
+import qualified Data.ByteString.Lazy.Char8 as B
 import Language.Haskell.LSP.Messages
 import Language.Haskell.LSP.Types
 import Language.Haskell.LSP.Test.Messages
+import Language.Haskell.LSP.Test.Decoding
+import System.IO
 import Control.Concurrent
 import Text.Parsec hiding (satisfy)
-import Control.Monad
 
 data MessageParserState = MessageParserState
 
-type MessageParser = ParsecT (Chan FromServerMessage) MessageParserState IO
+data SessionContext = SessionContext
+  {
+    serverIn :: Handle,
+    rootDir :: FilePath,
+    messageChan :: Chan FromServerMessage,
+    requestMap :: MVar RequestMap
+  }
 
-notification :: MessageParser FromServerMessage
+newtype SessionState = SessionState
+  {
+    curReqId :: LspId
+  }
+
+type Session = ParsecT (Chan FromServerMessage) SessionState (ReaderT SessionContext IO)
+
+notification :: Session FromServerMessage
 notification = satisfy isServerNotification
 
-request :: MessageParser FromServerMessage
+request :: Session FromServerMessage
 request = satisfy isServerRequest
 
-response :: MessageParser FromServerMessage
+response :: Session FromServerMessage
 response = satisfy isServerResponse
 
+loggingNotification :: Session FromServerMessage
+loggingNotification = satisfy shouldSkip
+  where
+    shouldSkip (NotLogMessage _) = True
+    shouldSkip (NotShowMessage _) = True
+    shouldSkip (ReqShowMessage _) = True
+    shouldSkip _ = False
+
 satisfy :: (Stream s m a, Eq a, Show a) => (a -> Bool) -> ParsecT s u m a
 satisfy pred = tokenPrim show nextPos test
   where nextPos x _ _ = x
@@ -32,20 +57,7 @@ testLog = NotLogMessage (NotificationMessage "2.0" WindowLogMessage (LogMessageP
 
 testSymbols = RspDocumentSymbols (ResponseMessage "2.0" (IdRspInt 0) (Just (List [])) Nothing)
 
-instance Stream (Chan a) IO a where
+instance (MonadIO m) => Stream (Chan a) m a where
   uncons c = do
-    x <- readChan c
+    x <- liftIO $ readChan c
     return $ Just (x, c)
-
-test :: IO ()
-test = do
-  chan <- newChan
-  let parser = do
-        n <- count 2 notification
-        rsp <- response
-        return (n, rsp)
-  forkIO $ forM_ [testLog, testLog, testSymbols] $ \x -> do
-    writeChan chan x
-    threadDelay 1000000
-  x <- runParserT parser MessageParserState "" chan
-  print x
\ No newline at end of file
index 95e3d5e9eeb1dce39add9f5c89a104d7c54a9d17..401fd9815fd09e81db4f3af8dafeff13ebc2f2ad 100644 (file)
@@ -6,7 +6,8 @@ import           Control.Monad.IO.Class
 import           Control.Lens hiding (List)
 import           Language.Haskell.LSP.Test
 import           Language.Haskell.LSP.Test.Replay
-import           Language.Haskell.LSP.TH.DataTypesJSON
+import           Language.Haskell.LSP.Types
+import           Language.Haskell.LSP.Messages
 
 main = hspec $ do
   describe "manual session validation" $ 
@@ -17,8 +18,9 @@ main = hspec $ do
 
         sendNotification TextDocumentDidOpen (DidOpenTextDocumentParams docItem)
 
-        (NotificationMessage _ TextDocumentPublishDiagnostics (PublishDiagnosticsParams _ (List diags))) <-
-          getMessage :: Session PublishDiagnosticsNotification
+        skipMany loggingNotification
+
+        (NotPublishDiagnostics (NotificationMessage _ TextDocumentPublishDiagnostics (PublishDiagnosticsParams _ (List diags)))) <- notification
 
         liftIO $ diags `shouldBe` []
         
@@ -26,7 +28,8 @@ main = hspec $ do
                     TextDocumentDocumentSymbol
                     (DocumentSymbolParams docId)
 
-        (ResponseMessage _ _ (Just (List symbols)) Nothing) <- getMessage :: Session DocumentSymbolsResponse
+        (RspDocumentSymbols (ResponseMessage _ _ (Just (List symbols)) Nothing)) <- response
+
         liftIO $ do
           let mainSymbol = head symbols
           mainSymbol ^. name `shouldBe` "main"