Add config option to log stderr
[opengl.git] / src / Language / Haskell / LSP / Test / Replay.hs
1 -- | A testing tool for replaying captured client logs back to a server,
2 -- and validating that the server output matches up with another log.
3 module Language.Haskell.LSP.Test.Replay
4   ( replaySession
5   )
6 where
7
8 import           Prelude hiding (id)
9 import           Control.Concurrent
10 import           Control.Monad.IO.Class
11 import qualified Data.ByteString.Lazy.Char8    as B
12 import qualified Data.Text                     as T
13 import           Language.Haskell.LSP.Capture
14 import           Language.Haskell.LSP.Messages
15 import           Language.Haskell.LSP.Types as LSP hiding (error)
16 import           Data.Aeson
17 import           Data.Default
18 import           Data.List
19 import           Data.Maybe
20 import           Control.Lens hiding (List)
21 import           Control.Monad
22 import           System.IO
23 import           System.FilePath
24 import           Language.Haskell.LSP.Test
25 import           Language.Haskell.LSP.Test.Files
26 import           Language.Haskell.LSP.Test.Decoding
27 import           Language.Haskell.LSP.Test.Messages
28 import           Language.Haskell.LSP.Test.Server
29
30
31 -- | Replays a captured client output and 
32 -- makes sure it matches up with an expected response.
33 -- The session directory should have a captured session file in it
34 -- named "session.log".
35 replaySession :: String -- ^ The command to run the server.
36               -> FilePath -- ^ The recorded session directory.
37               -> IO ()
38 replaySession serverExe sessionDir = do
39
40   entries <- B.lines <$> B.readFile (sessionDir </> "session.log")
41
42   -- decode session
43   let unswappedEvents = map (fromJust . decode) entries
44
45   withServer serverExe False $ \serverIn serverOut pid -> do
46
47     events <- swapCommands pid <$> swapFiles sessionDir unswappedEvents
48
49     let clientEvents = filter isClientMsg events
50         serverEvents = filter isServerMsg events
51         clientMsgs = map (\(FromClient _ msg) -> msg) clientEvents
52         serverMsgs = filter (not . shouldSkip) $ map (\(FromServer _ msg) -> msg) serverEvents
53         requestMap = getRequestMap clientMsgs
54
55     reqSema <- newEmptyMVar
56     rspSema <- newEmptyMVar
57     passSema <- newEmptyMVar
58     mainThread <- myThreadId
59
60     sessionThread <- liftIO $ forkIO $
61       runSessionWithHandles serverIn
62                             serverOut
63                             (listenServer serverMsgs requestMap reqSema rspSema passSema mainThread)
64                             def
65                             sessionDir
66                             (sendMessages clientMsgs reqSema rspSema)
67     takeMVar passSema
68     killThread sessionThread
69
70   where
71     isClientMsg (FromClient _ _) = True
72     isClientMsg _                = False
73
74     isServerMsg (FromServer _ _) = True
75     isServerMsg _                = False
76
77 sendMessages :: [FromClientMessage] -> MVar LspId -> MVar LspIdRsp -> Session ()
78 sendMessages [] _ _ = return ()
79 sendMessages (nextMsg:remainingMsgs) reqSema rspSema =
80   handleClientMessage request response notification nextMsg
81  where
82   -- TODO: May need to prevent premature exit notification being sent
83   notification msg@(NotificationMessage _ Exit _) = do
84     liftIO $ putStrLn "Will send exit notification soon"
85     liftIO $ threadDelay 10000000
86     sendNotification' msg
87
88     liftIO $ error "Done"
89
90   notification msg@(NotificationMessage _ m _) = do
91     sendNotification' msg
92
93     liftIO $ putStrLn $ "Sent a notification " ++ show m
94
95     sendMessages remainingMsgs reqSema rspSema
96
97   request msg@(RequestMessage _ id m _) = do
98     sendRequest' msg
99     liftIO $ putStrLn $  "Sent a request id " ++ show id ++ ": " ++ show m ++ "\nWaiting for a response"
100
101     rsp <- liftIO $ takeMVar rspSema
102     when (responseId id /= rsp) $
103       error $ "Expected id " ++ show id ++ ", got " ++ show rsp
104
105     sendMessages remainingMsgs reqSema rspSema
106
107   response msg@(ResponseMessage _ id _ _) = do
108     liftIO $ putStrLn $ "Waiting for request id " ++ show id ++ " from the server"
109     reqId <- liftIO $ takeMVar reqSema
110     if responseId reqId /= id
111       then error $ "Expected id " ++ show reqId ++ ", got " ++ show reqId
112       else do
113         sendResponse msg
114         liftIO $ putStrLn $ "Sent response to request id " ++ show id
115
116     sendMessages remainingMsgs reqSema rspSema
117
118
119 isNotification :: FromServerMessage -> Bool
120 isNotification (NotPublishDiagnostics      _) = True
121 isNotification (NotLogMessage              _) = True
122 isNotification (NotShowMessage             _) = True
123 isNotification (NotCancelRequestFromServer _) = True
124 isNotification _                              = False
125
126 listenServer :: [FromServerMessage] -> RequestMap -> MVar LspId -> MVar LspIdRsp -> MVar () -> ThreadId -> Handle -> Session ()
127 listenServer [] _ _ _ passSema _ _ = liftIO $ putMVar passSema ()
128 listenServer expectedMsgs reqMap reqSema rspSema passSema mainThreadId serverOut  = do
129
130   msgBytes <- liftIO $ getNextMessage serverOut
131   let msg = decodeFromServerMsg reqMap msgBytes
132
133   handleServerMessage request response notification msg
134
135   if shouldSkip msg
136     then listenServer expectedMsgs reqMap reqSema rspSema passSema mainThreadId serverOut
137     else if inRightOrder msg expectedMsgs
138       then listenServer (delete msg expectedMsgs) reqMap reqSema rspSema passSema mainThreadId serverOut
139       else let remainingMsgs = takeWhile (not . isNotification) expectedMsgs
140                 ++ [head $ dropWhile isNotification expectedMsgs]
141                exc = ReplayOutOfOrderException msg remainingMsgs
142             in liftIO $ throwTo mainThreadId exc
143
144   where
145   response :: ResponseMessage a -> Session ()
146   response res = do
147     liftIO $ putStrLn $ "Got response for id " ++ show (res ^. id)
148
149     liftIO $ putMVar rspSema (res ^. id) -- unblock the handler waiting to send a request
150
151   request :: RequestMessage ServerMethod a b -> Session ()
152   request req = do
153     liftIO
154       $  putStrLn
155       $  "Got request for id "
156       ++ show (req ^. id)
157       ++ " "
158       ++ show (req ^. method)
159
160     liftIO $ putMVar reqSema (req ^. id) -- unblock the handler waiting for a response
161
162   notification :: NotificationMessage ServerMethod a -> Session ()
163   notification n = liftIO $ putStrLn $ "Got notification " ++ show (n ^. method)
164
165
166
167 -- TODO: QuickCheck tests?
168 -- | Checks wether or not the message appears in the right order
169 -- @ N1 N2 N3 REQ1 N4 N5 REQ2 RES1 @
170 -- given N2, notification order doesn't matter.
171 -- @ N1 N3 REQ1 N4 N5 REQ2 RES1 @
172 -- given REQ1
173 -- @ N1 N3 N4 N5 REQ2 RES1 @
174 -- given RES1
175 -- @ N1 N3 N4 N5 XXXX RES1 @ False!
176 -- Order of requests and responses matter
177 inRightOrder :: FromServerMessage -> [FromServerMessage] -> Bool
178
179 inRightOrder _ [] = error "Why is this empty"
180
181 inRightOrder received (expected : msgs)
182   | received == expected               = True
183   | isNotification expected            = inRightOrder received msgs
184   | otherwise                          = False
185
186 -- | Ignore logging notifications since they vary from session to session
187 shouldSkip :: FromServerMessage -> Bool
188 shouldSkip (NotLogMessage  _) = True
189 shouldSkip (NotShowMessage _) = True
190 shouldSkip (ReqShowMessage _) = True
191 shouldSkip _                  = False
192
193 -- | Swaps out any commands uniqued with process IDs to match the specified process ID
194 swapCommands :: Int -> [Event] -> [Event]
195 swapCommands _ [] = []
196
197 swapCommands pid (FromClient t (ReqExecuteCommand req):xs) =  FromClient t (ReqExecuteCommand swapped):swapCommands pid xs
198   where swapped = params . command .~ newCmd $ req
199         newCmd = swapPid pid (req ^. params . command)
200
201 swapCommands pid (FromServer t (RspInitialize rsp):xs) = FromServer t (RspInitialize swapped):swapCommands pid xs
202   where swapped = case newCommands of
203           Just cmds -> result . _Just . LSP.capabilities . executeCommandProvider . _Just . commands .~ cmds $ rsp
204           Nothing -> rsp
205         oldCommands = rsp ^? result . _Just . LSP.capabilities . executeCommandProvider . _Just . commands
206         newCommands = fmap (fmap (swapPid pid)) oldCommands
207
208 swapCommands pid (x:xs) = x:swapCommands pid xs
209
210 hasPid :: T.Text -> Bool
211 hasPid = (>= 2) . T.length . T.filter (':' ==)
212 swapPid :: Int -> T.Text -> T.Text
213 swapPid pid t
214   | hasPid t = T.append (T.pack $ show pid) $ T.dropWhile (/= ':') t
215   | otherwise = t