Allow message types to be infered
authorLuke Lau <luke_lau@icloud.com>
Sat, 9 Jun 2018 22:11:37 +0000 (18:11 -0400)
committerLuke Lau <luke_lau@icloud.com>
Sat, 9 Jun 2018 22:11:37 +0000 (18:11 -0400)
example/Main.hs
src/Language/Haskell/LSP/Test.hs
src/Language/Haskell/LSP/Test/Decoding.hs
src/Language/Haskell/LSP/Test/Files.hs
src/Language/Haskell/LSP/Test/Parsing.hs
test/ParsingTests.hs
test/Test.hs

index d66e17e11075f0f018e7ee8a37eaf4410734212a..1697ca53d90cd51b2144b2d438efbc00ab568c70 100644 (file)
@@ -11,8 +11,8 @@ main = runSession "test/recordings/renamePass" $ do
 
   sendNotification TextDocumentDidOpen (DidOpenTextDocumentParams docItem)
   
-  sendRequest (Proxy :: Proxy DocumentSymbolRequest) TextDocumentDocumentSymbol (DocumentSymbolParams docId)
+  sendRequest TextDocumentDocumentSymbol (DocumentSymbolParams docId)
 
   skipMany loggingNotification
 
-  response >>= liftIO . print
\ No newline at end of file
+  anyResponse >>= liftIO . print
index 2e0926a58539581e2053cc14d4fff750e8424f3f..f4fb5c15021aa7563395feb5a405d7eb38ca032f 100644 (file)
@@ -24,8 +24,11 @@ module Language.Haskell.LSP.Test
   , sendNotification'
   , sendResponse
   -- * Receving
+  , anyRequest
   , request
+  , anyResponse
   , response
+  , anyNotification
   , notification
   , loggingNotification
   , publishDiagnosticsNotification
@@ -61,17 +64,15 @@ import Control.Applicative.Combinators
 import Control.Monad
 import Control.Monad.IO.Class
 import Control.Concurrent
-import Control.Lens
+import Control.Lens hiding ((.=))
 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 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.Test.Compat
 import System.IO
 import System.Directory
@@ -97,8 +98,8 @@ runSession rootDir session = do
   runSessionWithHandler listenServer rootDir $ do
 
     -- Wrap the session around initialize and shutdown calls
-    sendRequest (Proxy :: Proxy InitializeRequest) Initialize initializeParams
-    RspInitialize initRsp <- response
+    sendRequest Initialize initializeParams
+    initRsp <- response :: Session InitializeResponse
     liftIO $ maybe (return ()) (putStrLn . ("Error while initializing: " ++) . show ) (initRsp ^. LSP.error)
 
     sendNotification Initialized InitializedParams
@@ -159,29 +160,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
 
index f71a52fe9620641a87cae74bfdbd8686d1346e13..f8d63060cd269e71ab4757eb7695cf1b36b43a33 100644 (file)
@@ -51,8 +51,8 @@ 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
+updateRequestMap :: RequestMap -> LspId -> ClientMethod -> RequestMap
+updateRequestMap reqMap id method = HM.insert id method reqMap
 
 getRequestMap :: [FromClientMessage] -> RequestMap
 getRequestMap = foldl helper HM.empty
index f82df65cf6cef89640538575cffb69923c32934e..deb89e84c06a8b1be92d1c8bdda61e957c4debbd 100644 (file)
@@ -50,7 +50,7 @@ mapUris f event =
     fromClientMsg (NotWillSaveTextDocument n) = NotWillSaveTextDocument $ swapUri (params . textDocument) n
     fromClientMsg (NotDidSaveTextDocument n) = NotDidSaveTextDocument $ swapUri (params . textDocument) n
     fromClientMsg (NotDidCloseTextDocument n) = NotDidCloseTextDocument $ swapUri (params . textDocument) n
-    fromClientMsg (ReqInitialize r) = ReqInitialize $ params .~ (transformInit (r ^. params)) $ r
+    fromClientMsg (ReqInitialize r) = ReqInitialize $ params .~ transformInit (r ^. params) $ r
     fromClientMsg (ReqDocumentSymbols r) = ReqDocumentSymbols $ swapUri (params . textDocument) r
     fromClientMsg (ReqRename r) = ReqRename $ swapUri (params . textDocument) r
     fromClientMsg x = x
index fdd01c2a047b7d620ee606334ae96c9805a01ee3..2e829f372284373fa6d5673f9509e140c250387e 100644 (file)
@@ -1,21 +1,26 @@
 {-# LANGUAGE MultiParamTypeClasses #-}
 {-# LANGUAGE FlexibleInstances #-}
+{-# LANGUAGE ScopedTypeVariables #-}
+{-# LANGUAGE RankNTypes #-}
 module Language.Haskell.LSP.Test.Parsing where
 
 import Control.Applicative
+import Control.Concurrent.Chan
+import Control.Concurrent.MVar
 import Control.Monad.Trans.Class
 import Control.Monad.IO.Class
 import Control.Monad.Trans.Reader
 import Control.Monad.Trans.State
+import Data.Aeson
+import qualified Data.ByteString.Lazy.Char8 as B
+import Data.Conduit hiding (await)
+import Data.Conduit.Parser
+import Data.Maybe
 import Language.Haskell.LSP.Messages
-import Language.Haskell.LSP.Types hiding (error)
-import Language.Haskell.LSP.Test.Messages
+import Language.Haskell.LSP.Types 
 import Language.Haskell.LSP.Test.Decoding
+import Language.Haskell.LSP.Test.Messages
 import System.IO
-import Control.Concurrent.Chan
-import Control.Concurrent.MVar
-import Data.Conduit hiding (await)
-import Data.Conduit.Parser
 
 data SessionContext = SessionContext
   {
@@ -46,16 +51,39 @@ type ParserStateReader a s r m = ConduitParser a (StateT s (ReaderT r m))
 type Session = ParserStateReader FromServerMessage SessionState SessionContext IO
 
 -- | Matches if the message is a notification.
-notification :: Monad m => ConduitParser FromServerMessage m FromServerMessage
-notification = satisfy isServerNotification
+anyNotification :: Monad m => ConduitParser FromServerMessage m FromServerMessage
+anyNotification = satisfy isServerNotification
+
+notification :: forall m a. (Monad m, FromJSON a) => ConduitParser FromServerMessage m (NotificationMessage ServerMethod a)
+notification = do
+  let parser = decode . encodeMsg :: FromServerMessage -> Maybe (NotificationMessage ServerMethod a)
+  x <- satisfy (isJust . parser)
+  return $ fromJust $ decode $ encodeMsg x
 
 -- | Matches if the message is a request.
-request :: Monad m => ConduitParser FromServerMessage m FromServerMessage
-request = satisfy isServerRequest
+anyRequest :: Monad m => ConduitParser FromServerMessage m FromServerMessage
+anyRequest = satisfy isServerRequest
+
+request :: forall m a b. (Monad m, FromJSON a, FromJSON b) => ConduitParser FromServerMessage m (RequestMessage ServerMethod a b)
+request = do
+  let parser = decode . encodeMsg :: FromServerMessage -> Maybe (RequestMessage ServerMethod a b)
+  x <- satisfy (isJust . parser)
+  return $ fromJust $ decode $ encodeMsg x
 
 -- | Matches if the message is a response.
-response :: Monad m => ConduitParser FromServerMessage m FromServerMessage
-response = satisfy isServerResponse
+anyResponse :: Monad m => ConduitParser FromServerMessage m FromServerMessage
+anyResponse = satisfy isServerResponse
+
+response :: forall m a. (Monad m, FromJSON a) => ConduitParser FromServerMessage m (ResponseMessage a)
+response = do
+  let parser = decode . encodeMsg :: FromServerMessage -> Maybe (ResponseMessage a)
+  x <- satisfy (isJust . parser)
+  return $ fromJust $ decode $ encodeMsg x
+
+-- | A version of encode that encodes FromServerMessages as if they
+-- weren't wrapped.
+encodeMsg :: FromServerMessage -> B.ByteString
+encodeMsg = encode . genericToJSON (defaultOptions { sumEncoding = UntaggedValue })
 
 -- | Matches if the message is a log message notification or a show message notification/request.
 loggingNotification :: Monad m => ConduitParser FromServerMessage m FromServerMessage
index 7824ef3b4f7ff930388b7f3ebcd53274c21f901d..c8977b53e33f6915be4aae84bfa19d0c88b89578 100644 (file)
@@ -18,10 +18,9 @@ parsingSpec =
                                        (PublishDiagnosticsParams (Uri "foo")
                                                                  (List [])))
     it "get picked up" $ do
-      let 
-          source = yield testDiag
+      let source = yield testDiag
           session = do
-            diags <- publishDiagnosticsNotification
+            diags <- publishDiagnosticsNotification :: ConduitParser FromServerMessage IO PublishDiagnosticsNotification
             return $ diags ^. params . uri
       runConduit (source .| runConduitParser session) `shouldReturn` Uri "foo"
     it "get picked up after skipping others before" $ do
@@ -33,6 +32,6 @@ parsingSpec =
           notTestDiag = NotLogMessage (NotificationMessage "2.0" WindowLogMessage (LogMessageParams MtLog "foo"))
           source = yield notTestDiag >> yield testDiag
           session = do
-            diags <- skipManyTill notification publishDiagnosticsNotification
+            diags <- skipManyTill anyNotification notification :: ConduitParser FromServerMessage IO PublishDiagnosticsNotification
             return $ diags ^. params . uri
       runConduit (source .| runConduitParser session) `shouldReturn` Uri "foo"
index 652485e0af160279340ea8d6730dc37d33b075e9..ca135c7a379c3790f80e640262610b8887bde55b 100644 (file)
@@ -2,32 +2,28 @@
 {-# LANGUAGE OverloadedStrings #-}
 import           Test.Hspec
 import           Data.Maybe
-import           Data.Proxy
 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.Types
-import           Language.Haskell.LSP.Messages
 import           ParsingTests
 
 main = hspec $ do
-  describe "manual session validation" $ do
+  describe "manual session" $ do
     it "passes a test" $
       runSession "test/recordings/renamePass" $ do
         doc <- openDoc "Desktop/simple.hs" "haskell"
 
         skipMany loggingNotification
 
-        NotPublishDiagnostics diagsNot <- notification
+        diagsNot <- notification :: Session PublishDiagnosticsNotification
 
         liftIO $ diagsNot ^. params . diagnostics `shouldBe` List []
         
-        sendRequest (Proxy :: Proxy DocumentSymbolRequest)
-                    TextDocumentDocumentSymbol
-                    (DocumentSymbolParams doc)
+        sendRequest TextDocumentDocumentSymbol (DocumentSymbolParams doc)
 
-        RspDocumentSymbols rspSymbols <- response
+        rspSymbols <- response :: Session DocumentSymbolsResponse
         
         liftIO $ do
           let (List symbols) = fromJust (rspSymbols ^. result)
@@ -42,7 +38,7 @@ main = hspec $ do
       let session = runSession "test/recordings/renamePass" $ do
                       openDoc "Desktop/simple.hs" "haskell"
                       skipMany loggingNotification
-                    request
+                      anyRequest
         in session `shouldThrow` anyException
   
   describe "replay session" $ do