Add test for failing replay
authorLuke Lau <luke_lau@icloud.com>
Fri, 8 Jun 2018 19:51:24 +0000 (15:51 -0400)
committerLuke Lau <luke_lau@icloud.com>
Fri, 8 Jun 2018 19:51:24 +0000 (15:51 -0400)
Fix error message

src/Language/Haskell/LSP/Test/Replay.hs
test/Test.hs
test/recordings/renameFail/Desktop/simple.hs [new file with mode: 0644]
test/recordings/renameFail/session.log [new file with mode: 0644]

index 72fb0d6e2541706dee6ec2c7d3a214961918c8c9..2b55382959dd109e0b2a4beec982699db48f4361 100644 (file)
@@ -129,7 +129,7 @@ listenServer expectedMsgs reqMap reqSema rspSema passVar serverOut  = do
         print msg
         putStrLn "Expected one of:"
         mapM_ print $ takeWhile (not . isNotification) expectedMsgs
-        print $ head $ dropWhile (not . isNotification) expectedMsgs
+        print $ head $ dropWhile isNotification expectedMsgs
         putMVar passVar False
 
   where
index fd2466677b3c80702f25482dc5e515225e8eb142..1fd58da97d33508f47683c03194ef191076e5553 100644 (file)
@@ -36,6 +36,8 @@ main = hspec $ do
           mainSymbol ^. location . range `shouldBe` Range (Position 3 0) (Position 3 4)
           mainSymbol ^. containerName `shouldBe` Nothing
   
-  describe "replay session" $
+  describe "replay session" $ do
     it "passes a test" $
       replaySession "test/recordings/renamePass" `shouldReturn` True
+    it "fails a test" $
+      replaySession "test/recordings/renameFail" `shouldReturn` False
\ No newline at end of file
diff --git a/test/recordings/renameFail/Desktop/simple.hs b/test/recordings/renameFail/Desktop/simple.hs
new file mode 100644 (file)
index 0000000..f58bbd0
--- /dev/null
@@ -0,0 +1,76 @@
+module Main where
+
+main :: IO ()
+main = do
+  let initialList = []
+  interactWithUser initialList
+
+type Item = String
+type Items = [Item]
+
+data Command = Quit
+             | DisplayItems
+             | AddItem String
+             | RemoveItem Int
+             | Help
+
+type Error = String
+
+parseCommand :: String -> Either Error Command
+parseCommand line = case words line of
+  ["quit"] -> Right Quit
+  ["items"] -> Right DisplayItems
+  "add" : item -> Right $ AddItem $ unwords item
+  "remove" : i -> Right $ RemoveItem $ read $ unwords i
+  ["help"] -> Right Help
+  _ -> Left "Unknown command"
+
+addItem :: Item -> Items -> Items
+addItem = (:)
+
+displayItems :: Items -> String
+displayItems = unlines . map ("- " ++)
+
+removeItem :: Int -> Items -> Either Error Items
+removeItem i items
+  | i < 0 || i >= length items = Left "Out of range"
+  | otherwise = Right result
+  where (front, back) = splitAt (i + 1) items
+        result = init front ++ back
+
+interactWithUser :: Items -> IO ()
+interactWithUser items = do
+  line <- getLine
+  case parseCommand line of
+    Right DisplayItems -> do
+      putStrLn $ displayItems items
+      interactWithUser items
+
+    Right (AddItem item) -> do
+      let newItems = addItem item items
+      putStrLn "Added"
+      interactWithUser newItems
+
+    Right (RemoveItem i) ->
+      case removeItem i items of
+        Right newItems -> do
+          putStrLn $ "Removed " ++ items !! i
+          interactWithUser newItems
+        Left err -> do
+          putStrLn err
+          interactWithUser items
+
+
+    Right Quit -> return ()
+
+    Right Help -> do
+      putStrLn "Commands:"
+      putStrLn "help"
+      putStrLn "items"
+      putStrLn "add"
+      putStrLn "quit"
+      interactWithUser items
+
+    Left err -> do
+      putStrLn $ "Error: " ++ err
+      interactWithUser items
diff --git a/test/recordings/renameFail/session.log b/test/recordings/renameFail/session.log
new file mode 100644 (file)
index 0000000..99246af
--- /dev/null
@@ -0,0 +1,18 @@
+{"tag":"FromClient","contents":["2018-06-03T04:08:38.856591Z",{"tag":"ReqInitialize","contents":{"jsonrpc":"2.0","params":{"rootUri":"file:///Users/luke","processId":7558,"rootPath":"/Users/luke","capabilities":{"textDocument":{"completion":{"completionItem":{"snippetSupport":false}}}},"trace":"off"},"method":"initialize","id":9}}]}
+{"tag":"FromServer","contents":["2018-06-03T04:08:38.873087Z",{"tag":"RspInitialize","contents":{"result":{"capabilities":{"textDocumentSync":{"openClose":true,"change":2,"willSave":false,"willSaveWaitUntil":false,"save":{"includeText":false}},"documentRangeFormattingProvider":true,"documentHighlightProvider":true,"executeCommandProvider":{"commands":["applyrefact:applyOne","hare:demote"]},"renameProvider":true,"definitionProvider":true,"hoverProvider":true,"codeActionProvider":true,"completionProvider":{"triggerCharacters":["."],"resolveProvider":true},"documentSymbolProvider":true,"documentFormattingProvider":true,"referencesProvider":true}},"jsonrpc":"2.0","id":9}}]}
+{"tag":"FromClient","contents":["2018-06-03T04:08:39.325465Z",{"tag":"NotInitialized","contents":{"jsonrpc":"2.0","params":{},"method":"initialized"}}]}
+{"tag":"FromClient","contents":["2018-06-03T04:08:39.325807Z",{"tag":"NotDidChangeConfiguration","contents":{"jsonrpc":"2.0","params":{"settings":{}},"method":"workspace/didChangeConfiguration"}}]}
+{"tag":"FromClient","contents":["2018-06-03T04:08:39.326177Z",{"tag":"NotDidOpenTextDocument","contents":{"jsonrpc":"2.0","params":{"textDocument":{"languageId":"haskell","text":"module Main where\n\nmain :: IO ()\nmain = do\n  let initialList = []\n  interactWithUser initialList\n\ntype Item = String\ntype Items = [Item]\n\ndata Command = Quit\n             | DisplayItems\n             | AddItem String\n             | RemoveItem Int\n             | Help\n\ntype Error = String\n\nparseCommand :: String -> Either Error Command\nparseCommand line = case words line of\n  [\"quit\"] -> Right Quit\n  [\"items\"] -> Right DisplayItems\n  \"add\" : item -> Right $ AddItem $ unwords item\n  \"remove\" : i -> Right $ RemoveItem $ read $ unwords i\n  [\"help\"] -> Right Help\n  _ -> Left \"Unknown command\"\n\naddItem :: Item -> Items -> Items\naddItem = (:)\n\ndisplayItems :: Items -> String\ndisplayItems = unlines . map (\"- \" ++)\n\nremoveItem :: Int -> Items -> Either Error Items\nremoveItem i items\n  | i < 0 || i >= length items = Left \"Out of range\"\n  | otherwise = Right result\n  where (front, back) = splitAt (i + 1) items\n        result = init front ++ back\n\ninteractWithUser :: Items -> IO ()\ninteractWithUser items = do\n  line <- getLine\n  case parseCommand line of\n    Right DisplayItems -> do\n      putStrLn $ displayItems items\n      interactWithUser items\n\n    Right (AddItem item) -> do\n      let newItems = addItem item items\n      putStrLn \"Added\"\n      interactWithUser newItems\n\n    Right (RemoveItem i) ->\n      case removeItem i items of\n        Right newItems -> do\n          putStrLn $ \"Removed \" ++ items !! i\n          interactWithUser newItems\n        Left err -> do\n          putStrLn err\n          interactWithUser items\n\n\n    Right Quit -> return ()\n\n    Right Help -> do\n      putStrLn \"Commands:\"\n      putStrLn \"help\"\n      putStrLn \"items\"\n      putStrLn \"add\"\n      putStrLn \"quit\"\n      interactWithUser items\n\n    Left err -> do\n      putStrLn $ \"Error: \" ++ err\n      interactWithUser items\n","uri":"file:///Users/luke/Desktop/simple.hs","version":0}},"method":"textDocument/didOpen"}}]}
+{"tag":"FromServer","contents":["2018-06-03T04:08:39.327288Z",{"tag":"NotLogMessage","contents":{"jsonrpc":"2.0","params":{"type":1,"message":"haskell-lsp:didChangeConfiguration error. NotificationMessage {_jsonrpc = \"2.0\", _method = WorkspaceDidChangeConfiguration, _params = DidChangeConfigurationParams {_settings = Object (fromList [])}} \"key \\\"languageServerHaskell\\\" not present\""},"method":"window/logMessage"}}]}
+{"tag":"FromServer","contents":["2018-06-03T04:08:39.327577Z",{"tag":"NotLogMessage","contents":{"jsonrpc":"2.0","params":{"type":4,"message":"Using hie version: Version 0.2.0.0, Git revision c34c08eeced8173983601e98304258075f3057e1 (1459 commits) x86_64 ghc-8.4.3"},"method":"window/logMessage"}}]}
+{"tag":"FromServer","contents":["2018-06-03T04:08:39.328266Z",{"tag":"NotLogMessage","contents":{"jsonrpc":"2.0","params":{"type":4,"message":"Using hoogle db at: /Users/luke/.hoogle/default-haskell-5.0.17.hoo"},"method":"window/logMessage"}}]}
+{"tag":"FromServer","contents":["2018-06-03T04:08:39.524239Z",{"tag":"NotPublishDiagnostics","contents":{"jsonrpc":"2.0","params":{"uri":"file:///Users/luke/Desktop/simple.hs","diagnostics":[]},"method":"textDocument/publishDiagnostics"}}]}
+{"tag":"FromServer","contents":["2018-06-03T04:08:39.714012Z",{"tag":"NotPublishDiagnostics","contents":{"jsonrpc":"2.0","params":{"uri":"file:///Users/luke/Desktop/simple.hs","diagnostics":[]},"method":"textDocument/publishDiagnostics"}}]}
+{"tag":"FromClient","contents":["2018-06-03T04:08:40.844374Z",{"tag":"ReqDocumentSymbols","contents":{"jsonrpc":"2.0","params":{"textDocument":{"uri":"file:///Users/luke/Desktop/simple.hs"}},"method":"textDocument/documentSymbol","id":25}}]}
+{"tag":"FromServer","contents":["2018-06-03T04:08:40.859268Z",{"tag":"RspDocumentSymbols","contents":{"result":[{"location":{"uri":"file:///Users/luke/Desktop/simple.hs","range":{"start":{"line":7,"character":5},"end":{"line":7,"character":9}}},"kind":5,"name":"Item"},{"location":{"uri":"file:///Users/luke/Desktop/simple.hs","range":{"start":{"line":8,"character":5},"end":{"line":8,"character":10}}},"kind":5,"name":"Items"},{"location":{"uri":"file:///Users/luke/Desktop/simple.hs","range":{"start":{"line":10,"character":5},"end":{"line":10,"character":12}}},"kind":5,"name":"Command"},{"location":{"uri":"file:///Users/luke/Desktop/simple.hs","range":{"start":{"line":10,"character":15},"end":{"line":10,"character":19}}},"kind":9,"containerName":"Command","name":"Quit"},{"location":{"uri":"file:///Users/luke/Desktop/simple.hs","range":{"start":{"line":11,"character":15},"end":{"line":11,"character":27}}},"kind":9,"containerName":"Command","name":"DisplayItems"},{"location":{"uri":"file:///Users/luke/Desktop/simple.hs","range":{"start":{"line":12,"character":15},"end":{"line":12,"character":22}}},"kind":9,"containerName":"Command","name":"AddItem"},{"location":{"uri":"file:///Users/luke/Desktop/simple.hs","range":{"start":{"line":13,"character":15},"end":{"line":13,"character":25}}},"kind":9,"containerName":"Command","name":"RemoveItem"},{"location":{"uri":"file:///Users/luke/Desktop/simple.hs","range":{"start":{"line":14,"character":15},"end":{"line":14,"character":19}}},"kind":9,"containerName":"Command","name":"Help"},{"location":{"uri":"file:///Users/luke/Desktop/simple.hs","range":{"start":{"line":16,"character":5},"end":{"line":16,"character":10}}},"kind":5,"name":"Error"},{"location":{"uri":"file:///Users/luke/Desktop/simple.hs","range":{"start":{"line":19,"character":0},"end":{"line":19,"character":12}}},"kind":12,"name":"parseCommand"},{"location":{"uri":"file:///Users/luke/Desktop/simple.hs","range":{"start":{"line":28,"character":0},"end":{"line":28,"character":7}}},"kind":12,"name":"addItem"},{"location":{"uri":"file:///Users/luke/Desktop/simple.hs","range":{"start":{"line":31,"character":0},"end":{"line":31,"character":12}}},"kind":12,"name":"displayItems"},{"location":{"uri":"file:///Users/luke/Desktop/simple.hs","range":{"start":{"line":34,"character":0},"end":{"line":34,"character":10}}},"kind":12,"name":"removeItem"},{"location":{"uri":"file:///Users/luke/Desktop/simple.hs","range":{"start":{"line":41,"character":0},"end":{"line":41,"character":16}}},"kind":12,"name":"interactWithUser"}],"jsonrpc":"2.0","id":25}}]}
+{"tag":"FromClient","contents":["2018-06-03T04:08:46.24927Z",{"tag":"ReqRename","contents":{"jsonrpc":"2.0","params":{"newName":"arseCommand","textDocument":{"uri":"file:///Users/luke/Desktop/simple.hs"},"position":{"line":19,"character":0}},"method":"textDocument/rename","id":32}}]}
+{"tag":"FromServer","contents":["2018-06-03T04:08:46.528715Z",{"tag":"RspRename","contents":{"result":{"changes":{"file:///Users/luke/Desktop/simple.hs":[{"range":{"start":{"line":43,"character":0},"end":{"line":43,"character":27}},"newText":"  case arseCommand line of"},{"range":{"start":{"line":18,"character":0},"end":{"line":19,"character":38}},"newText":"arseCommand :: String -> Either Error Command\narseCommand line = case words line of"}]}},"jsonrpc":"2.0","id":32}}]}
+{"tag":"FromClient","contents":["2018-06-03T04:08:48.300837Z",{"tag":"NotDidChangeTextDocument","contents":{"jsonrpc":"2.0","params":{"contentChanges":[{"text":"module Main where\n\nmain :: IO ()\nmain = do\n  let initialList = []\n  interactWithUser initialList\n\ntype Item = String\ntype Items = [Item]\n\ndata Command = Quit\n             | DisplayItems\n             | AddItem String\n             | RemoveItem Int\n             | Help\n\ntype Error = String\n\narseCommand :: String -> Either Error Command\narseCommand line = case words line of\n  [\"quit\"] -> Right Quit\n  [\"items\"] -> Right DisplayItems\n  \"add\" : item -> Right $ AddItem $ unwords item\n  \"remove\" : i -> Right $ RemoveItem $ read $ unwords i\n  [\"help\"] -> Right Help\n  _ -> Left \"Unknown command\"\n\naddItem :: Item -> Items -> Items\naddItem = (:)\n\ndisplayItems :: Items -> String\ndisplayItems = unlines . map (\"- \" ++)\n\nremoveItem :: Int -> Items -> Either Error Items\nremoveItem i items\n  | i < 0 || i >= length items = Left \"Out of range\"\n  | otherwise = Right result\n  where (front, back) = splitAt (i + 1) items\n        result = init front ++ back\n\ninteractWithUser :: Items -> IO ()\ninteractWithUser items = do\n  line <- getLine\n  case arseCommand line of\n    Right DisplayItems -> do\n      putStrLn $ displayItems items\n      interactWithUser items\n\n    Right (AddItem item) -> do\n      let newItems = addItem item items\n      putStrLn \"Added\"\n      interactWithUser newItems\n\n    Right (RemoveItem i) ->\n      case removeItem i items of\n        Right newItems -> do\n          putStrLn $ \"Removed \" ++ items !! i\n          interactWithUser newItems\n        Left err -> do\n          putStrLn err\n          interactWithUser items\n\n\n    Right Quit -> return ()\n\n    Right Help -> do\n      putStrLn \"Commands:\"\n      putStrLn \"help\"\n      putStrLn \"items\"\n      putStrLn \"add\"\n      putStrLn \"quit\"\n      interactWithUser items\n\n    Left err -> do\n      putStrLn $ \"Error: \" ++ err\n      interactWithUser items\n"}],"textDocument":{"uri":"file:///Users/luke/Desktop/simple.hs","version":1}},"method":"textDocument/didChange"}}]}
+{"tag":"FromServer","contents":["2018-06-03T04:08:48.357517Z",{"tag":"NotPublishDiagnostics","contents":{"jsonrpc":"2.0","params":{"uri":"file:///Users/luke/Desktop/simple.hs","diagnostics":[]},"method":"textDocument/publishDiagnostics"}}]}
+{"tag":"FromServer","contents":["2018-06-03T04:08:48.397078Z",{"tag":"NotPublishDiagnostics","contents":{"jsonrpc":"2.0","params":{"uri":"file:///Users/luke/Desktop/simple.hs","diagnostics":[]},"method":"textDocument/publishDiagnostics"}}]}
+{"tag":"FromClient","contents":["2018-06-03T04:08:51.543574Z",{"tag":"NotExit","contents":{"jsonrpc":"2.0","params":null,"method":"exit"}}]}