Try out Chan Stream instance
authorLuke Lau <luke_lau@icloud.com>
Thu, 7 Jun 2018 02:15:02 +0000 (22:15 -0400)
committerLuke Lau <luke_lau@icloud.com>
Thu, 7 Jun 2018 02:15:02 +0000 (22:15 -0400)
src/Language/Haskell/LSP/Test/Parsing.hs

index de2ca860e65622c014ee0a85a8ecae9e8c2a1185..9d2dd702c78d2065b53835e12cc11a4f3dd4b9be 100644 (file)
@@ -1,14 +1,18 @@
 {-# LANGUAGE OverloadedStrings #-}
+{-# LANGUAGE MultiParamTypeClasses #-}
+{-# LANGUAGE FlexibleInstances #-}
 module Language.Haskell.LSP.Test.Parsing where
 
 import Language.Haskell.LSP.Messages
 import Language.Haskell.LSP.Types
 import Language.Haskell.LSP.Test.Messages
+import Control.Concurrent
 import Text.Parsec hiding (satisfy)
+import Control.Monad
 
 data MessageParserState = MessageParserState
 
-type MessageParser = Parsec [FromServerMessage] MessageParserState
+type MessageParser = ParsecT (Chan FromServerMessage) MessageParserState IO
 
 notification :: MessageParser FromServerMessage
 notification = satisfy isServerNotification
@@ -28,5 +32,20 @@ testLog = NotLogMessage (NotificationMessage "2.0" WindowLogMessage (LogMessageP
 
 testSymbols = RspDocumentSymbols (ResponseMessage "2.0" (IdRspInt 0) (Just (List [])) Nothing)
 
-parseMessages :: MessageParser a -> [FromServerMessage] -> Either ParseError a
-parseMessages parser = runP parser MessageParserState ""
\ No newline at end of file
+instance Stream (Chan a) IO a where
+  uncons c = do
+    x <- 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