Skip to content

Commit 813e665

Browse files
mpickeringalt-romes
authored andcommitted
Fix race conditions due to MVar usage
The lock `dap` takes on the MVar could cause a nasty deadlock while doing something seemingly standard in the debugger threads that are launched by registerNewDebugSession. Consider (readDebuggerOutput, writeDebuggerOutput) <- liftIO P.createPipe registerNewDebugSession (maybe "debug-session" T.pack __sessionId) DAS{..} [ debuggerThread ... writeDebuggerOutput , outputEventsThread readDebuggerOutput ] An outline of the deadlock is: 1. Initialisation starts, starts writing to a pipe 2. Worker thread tries to output things from the pipe, but can't because that requires taking a lock on the MVar 3. Step 1 blocks because the pipe gets full 4. Step 2 blocks, since it is waiting for step 1 to finish We fix this by getting rid of the `MVar` internally and adding a `ReaderT` to the stack transformer with a debugger-server-wide sessionId backed by an IORef. `Adaptor` now has an additional type parameter denoting the type of the request we are responding to. Crucially, this will be `Request` when responding to a DAP request (e.g. in `send***` functions). On the other hand, this will be `()` for the `withAdaptor` continuation argument of `registerNewDebugSession` which unlifts `Adaptor` to `IO` because, when unlifting, we are not replying to any request. These changes to the internal implementation of `Adaptor` which allow us to get rid of the `MVar` are sufficient to fix the deadlock and now avoid footguns uses of `withAdaptor`. Fixes #6
1 parent 544c4dc commit 813e665

File tree

7 files changed

+199
-167
lines changed

7 files changed

+199
-167
lines changed

CHANGELOG.md

+9
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,14 @@
11
# Revision history for dap
22

3+
## Unreleased -- YYYY-mm-dd
4+
5+
* `Adaptor` has an additional type parameter denoting the type of the request
6+
we are responding to. Crucially, this will be `Request` when responding to a
7+
DAP request (e.g. in `send***` functions).
8+
On the other hand, this will be `()` for the `withAdaptor` continuation
9+
argument of `registerNewDebugSession` which unlifts `Adaptor` to `IO`
10+
because, when unlifting, we are not replying to any request.
11+
312
## 0.1.0.0 -- YYYY-mm-dd
413

514
* First version. Released on an unsuspecting world.

src/DAP/Adaptor.hs

+95-66
Original file line numberDiff line numberDiff line change
@@ -50,15 +50,16 @@ module DAP.Adaptor
5050
-- * Internal function used to execute actions on behalf of the DAP server
5151
-- from child threads (useful for handling asynchronous debugger events).
5252
, runAdaptorWith
53+
, runAdaptor
5354
) where
5455
----------------------------------------------------------------------------
55-
import Control.Concurrent.MVar ( modifyMVar_, MVar )
5656
import Control.Concurrent.Lifted ( fork, killThread )
5757
import Control.Exception ( throwIO )
5858
import Control.Concurrent.STM ( atomically, readTVarIO, modifyTVar' )
5959
import Control.Monad ( when, unless )
6060
import Control.Monad.Except ( runExceptT, throwError )
61-
import Control.Monad.State ( runStateT, gets, MonadIO(liftIO), gets, modify' )
61+
import Control.Monad.State ( runStateT, gets, gets, modify' )
62+
import Control.Monad.Reader
6263
import Data.Aeson ( FromJSON, Result (..), fromJSON )
6364
import Data.Aeson.Encode.Pretty ( encodePretty )
6465
import Data.Aeson.Types ( object, Key, KeyValue((.=)), ToJSON )
@@ -68,23 +69,24 @@ import System.IO ( Handle )
6869
import qualified Data.ByteString.Lazy.Char8 as BL8
6970
import qualified Data.ByteString.Char8 as BS
7071
import qualified Data.HashMap.Strict as H
72+
import Data.IORef
7173
----------------------------------------------------------------------------
7274
import DAP.Types
7375
import DAP.Utils
7476
import DAP.Internal
7577
----------------------------------------------------------------------------
76-
logWarn :: BL8.ByteString -> Adaptor app ()
78+
logWarn :: BL8.ByteString -> Adaptor app r ()
7779
logWarn msg = logWithAddr WARN Nothing (withBraces msg)
7880
----------------------------------------------------------------------------
79-
logError :: BL8.ByteString -> Adaptor app ()
81+
logError :: BL8.ByteString -> Adaptor app r ()
8082
logError msg = logWithAddr ERROR Nothing (withBraces msg)
8183
----------------------------------------------------------------------------
82-
logInfo :: BL8.ByteString -> Adaptor app ()
84+
logInfo :: BL8.ByteString -> Adaptor app r ()
8385
logInfo msg = logWithAddr INFO Nothing (withBraces msg)
8486
----------------------------------------------------------------------------
8587
-- | Meant for internal consumption, used to signify a message has been
8688
-- SENT from the server
87-
debugMessage :: BL8.ByteString -> Adaptor app ()
89+
debugMessage :: BL8.ByteString -> Adaptor app r ()
8890
debugMessage msg = do
8991
shouldLog <- getDebugLogging
9092
addr <- getAddress
@@ -93,7 +95,7 @@ debugMessage msg = do
9395
$ logger DEBUG addr (Just SENT) msg
9496
----------------------------------------------------------------------------
9597
-- | Meant for external consumption
96-
logWithAddr :: Level -> Maybe DebugStatus -> BL8.ByteString -> Adaptor app ()
98+
logWithAddr :: Level -> Maybe DebugStatus -> BL8.ByteString -> Adaptor app r ()
9799
logWithAddr level status msg = do
98100
addr <- getAddress
99101
liftIO (logger level addr status msg)
@@ -113,38 +115,42 @@ logger level addr maybeDebug msg = do
113115
, msg
114116
]
115117
----------------------------------------------------------------------------
116-
getDebugLogging :: Adaptor app Bool
117-
getDebugLogging = gets (debugLogging . serverConfig)
118+
getDebugLogging :: Adaptor app r Bool
119+
getDebugLogging = asks (debugLogging . serverConfig)
118120
----------------------------------------------------------------------------
119-
getServerCapabilities :: Adaptor app Capabilities
120-
getServerCapabilities = gets (serverCapabilities . serverConfig)
121+
getServerCapabilities :: Adaptor app r Capabilities
122+
getServerCapabilities = asks (serverCapabilities . serverConfig)
121123
----------------------------------------------------------------------------
122-
getAddress :: Adaptor app SockAddr
123-
getAddress = gets address
124+
getAddress :: Adaptor app r SockAddr
125+
getAddress = asks address
124126
----------------------------------------------------------------------------
125-
getHandle :: Adaptor app Handle
126-
getHandle = gets handle
127+
getHandle :: Adaptor app r Handle
128+
getHandle = asks handle
127129
----------------------------------------------------------------------------
128-
getRequestSeqNum :: Adaptor app Seq
129-
getRequestSeqNum = gets (requestSeqNum . request)
130+
getRequestSeqNum :: Adaptor app Request Seq
131+
getRequestSeqNum = asks (requestSeqNum . request)
130132
----------------------------------------------------------------------------
131-
getDebugSessionId :: Adaptor app SessionId
133+
getDebugSessionId :: Adaptor app r SessionId
132134
getDebugSessionId = do
133-
gets sessionId >>= \case
135+
var <- asks (sessionId)
136+
res <- liftIO $ readIORef var
137+
case res of
134138
Nothing -> sessionNotFound
135139
Just sessionId -> pure sessionId
136140
where
137141
sessionNotFound = do
138142
let err = "No Debug Session has started"
139143
sendError (ErrorMessage (pack err)) Nothing
140144
----------------------------------------------------------------------------
141-
setDebugSessionId :: SessionId -> Adaptor app ()
142-
setDebugSessionId session = modify' $ \s -> s { sessionId = Just session }
145+
setDebugSessionId :: SessionId -> Adaptor app r ()
146+
setDebugSessionId session = do
147+
var <- asks sessionId
148+
liftIO $ writeIORef var (Just session)
143149
----------------------------------------------------------------------------
144150
registerNewDebugSession
145151
:: SessionId
146152
-> app
147-
-> [((Adaptor app () -> IO ()) -> IO ())]
153+
-> [(Adaptor app () () -> IO ()) -> IO ()]
148154
-- ^ Actions to run debugger (operates in a forked thread that gets killed when disconnect is set)
149155
-- Long running operation, meant to be used as a sink for
150156
-- the debugger to emit events and for the adaptor to forward to the editor
@@ -161,29 +167,32 @@ registerNewDebugSession
161167
-- > withAdaptor $ sendOutputEvent defaultOutputEvent { outputEventOutput = output }
162168
-- > ]
163169
--
164-
-> Adaptor app ()
170+
-> Adaptor app r ()
165171
registerNewDebugSession k v debuggerConcurrentActions = do
166-
store <- gets appStore
167-
adaptorStateMVar <- gets adaptorStateMVar
172+
store <- asks appStore
173+
lcl <- ask
174+
let lcl' = lcl { request = () }
175+
let emptyState = AdaptorState MessageTypeEvent []
168176
debuggerThreadState <- liftIO $
169177
DebuggerThreadState
170-
<$> sequence [fork $ action (runAdaptorWith adaptorStateMVar) | action <- debuggerConcurrentActions]
178+
<$> sequence [fork $ action (runAdaptorWith lcl' emptyState "s") | action <- debuggerConcurrentActions]
171179
liftIO . atomically $ modifyTVar' store (H.insert k (debuggerThreadState, v))
172-
setDebugSessionId k
173180
logInfo $ BL8.pack $ "Registered new debug session: " <> unpack k
181+
setDebugSessionId k
182+
174183
----------------------------------------------------------------------------
175-
updateDebugSession :: (app -> app) -> Adaptor app ()
184+
updateDebugSession :: (app -> app) -> Adaptor app r ()
176185
updateDebugSession updateFun = do
177186
sessionId <- getDebugSessionId
178-
store <- gets appStore
187+
store <- asks appStore
179188
liftIO . atomically $ modifyTVar' store (H.adjust (fmap updateFun) sessionId)
180189
----------------------------------------------------------------------------
181-
getDebugSession :: Adaptor a a
190+
getDebugSession :: Adaptor a r a
182191
getDebugSession = do
183192
(_, _, app) <- getDebugSessionWithThreadIdAndSessionId
184193
pure app
185194
----------------------------------------------------------------------------
186-
getDebugSessionWithThreadIdAndSessionId :: Adaptor app (SessionId, DebuggerThreadState, app)
195+
getDebugSessionWithThreadIdAndSessionId :: Adaptor app r (SessionId, DebuggerThreadState, app)
187196
getDebugSessionWithThreadIdAndSessionId = do
188197
sessionId <- getDebugSessionId
189198
appStore <- liftIO . readTVarIO =<< getAppStore
@@ -203,7 +212,7 @@ getDebugSessionWithThreadIdAndSessionId = do
203212
-- | Whenever a debug Session ends (cleanly or otherwise) this function
204213
-- will remove the local debugger communication state from the global state
205214
----------------------------------------------------------------------------
206-
destroyDebugSession :: Adaptor app ()
215+
destroyDebugSession :: Adaptor app r ()
207216
destroyDebugSession = do
208217
(sessionId, DebuggerThreadState {..}, _) <- getDebugSessionWithThreadIdAndSessionId
209218
store <- getAppStore
@@ -212,17 +221,17 @@ destroyDebugSession = do
212221
atomically $ modifyTVar' store (H.delete sessionId)
213222
logInfo $ BL8.pack $ "SessionId " <> unpack sessionId <> " ended"
214223
----------------------------------------------------------------------------
215-
getAppStore :: Adaptor app (AppStore app)
216-
getAppStore = gets appStore
224+
getAppStore :: Adaptor app r (AppStore app)
225+
getAppStore = asks appStore
217226
----------------------------------------------------------------------------
218-
getCommand :: Adaptor app Command
219-
getCommand = command <$> gets request
227+
getCommand :: Adaptor app Request Command
228+
getCommand = command <$> asks request
220229
----------------------------------------------------------------------------
221230
-- | 'sendRaw' (internal use only)
222231
-- Sends a raw JSON payload to the editor. No "seq", "type" or "command" fields are set.
223232
-- The message is still encoded with the ProtocolMessage Header, byte count, and CRLF.
224233
--
225-
sendRaw :: ToJSON value => value -> Adaptor app ()
234+
sendRaw :: ToJSON value => value -> Adaptor app r ()
226235
sendRaw value = do
227236
handle <- getHandle
228237
address <- getAddress
@@ -234,7 +243,7 @@ sendRaw value = do
234243
-- i.e. "request_seq" and "command".
235244
-- We also have to be sure to reset the message payload
236245
----------------------------------------------------------------------------
237-
send :: Adaptor app () -> Adaptor app ()
246+
send :: Adaptor app Request () -> Adaptor app Request ()
238247
send action = do
239248
() <- action
240249
cmd <- getCommand
@@ -258,9 +267,28 @@ send action = do
258267

259268
-- Send payload to client from debug adaptor
260269
writeToHandle address handle payload
270+
resetAdaptorStatePayload
271+
272+
sendEvent :: Adaptor app r () -> Adaptor app r ()
273+
sendEvent action = do
274+
() <- action
275+
handle <- getHandle
276+
messageType <- gets messageType
277+
address <- getAddress
278+
case messageType of
279+
MessageTypeResponse -> error "use send"
280+
MessageTypeRequest -> error "use send"
281+
MessageTypeEvent -> do
282+
address <- getAddress
283+
setField "type" messageType
261284

262-
-- Reset payload each time a send occurs
285+
-- Once all fields are set, fetch the payload for sending
286+
payload <- object <$> gets payload
287+
-- Send payload to client from debug adaptor
288+
writeToHandle address handle payload
263289
resetAdaptorStatePayload
290+
291+
264292
----------------------------------------------------------------------------
265293
-- | Writes payload to the given 'Handle' using the local connection lock
266294
----------------------------------------------------------------------------
@@ -269,31 +297,31 @@ writeToHandle
269297
=> SockAddr
270298
-> Handle
271299
-> event
272-
-> Adaptor app ()
300+
-> Adaptor app r ()
273301
writeToHandle _ handle evt = do
274302
let msg = encodeBaseProtocolMessage evt
275303
debugMessage ("\n" <> encodePretty evt)
276304
withConnectionLock (BS.hPutStr handle msg)
277305
----------------------------------------------------------------------------
278306
-- | Resets Adaptor's payload
279307
----------------------------------------------------------------------------
280-
resetAdaptorStatePayload :: Adaptor app ()
308+
resetAdaptorStatePayload :: Adaptor app r ()
281309
resetAdaptorStatePayload = modify' $ \s -> s { payload = [] }
282310
----------------------------------------------------------------------------
283-
sendSuccesfulResponse :: Adaptor app () -> Adaptor app ()
311+
sendSuccesfulResponse :: Adaptor app Request () -> Adaptor app Request ()
284312
sendSuccesfulResponse action = do
285313
send $ do
286314
setType MessageTypeResponse
287315
setSuccess True
288316
action
289317
----------------------------------------------------------------------------
290-
sendSuccesfulEmptyResponse :: Adaptor app ()
318+
sendSuccesfulEmptyResponse :: Adaptor app Request ()
291319
sendSuccesfulEmptyResponse = sendSuccesfulResponse (pure ())
292320
----------------------------------------------------------------------------
293321
-- | Sends successful event
294-
sendSuccesfulEvent :: EventType -> Adaptor app () -> Adaptor app ()
322+
sendSuccesfulEvent :: EventType -> Adaptor app r () -> Adaptor app r ()
295323
sendSuccesfulEvent event action = do
296-
send $ do
324+
sendEvent $ do
297325
setEvent event
298326
setType MessageTypeEvent
299327
action
@@ -305,7 +333,7 @@ sendSuccesfulEvent event action = do
305333
sendError
306334
:: ErrorMessage
307335
-> Maybe Message
308-
-> Adaptor app a
336+
-> Adaptor app r a
309337
sendError errorMessage maybeMessage = do
310338
throwError (errorMessage, maybeMessage)
311339
----------------------------------------------------------------------------
@@ -314,7 +342,7 @@ sendError errorMessage maybeMessage = do
314342
sendErrorResponse
315343
:: ErrorMessage
316344
-> Maybe Message
317-
-> Adaptor app ()
345+
-> Adaptor app Request ()
318346
sendErrorResponse errorMessage maybeMessage = do
319347
send $ do
320348
setType MessageTypeResponse
@@ -324,24 +352,24 @@ sendErrorResponse errorMessage maybeMessage = do
324352
----------------------------------------------------------------------------
325353
setErrorMessage
326354
:: ErrorMessage
327-
-> Adaptor app ()
355+
-> Adaptor app r ()
328356
setErrorMessage v = setField "message" v
329357
----------------------------------------------------------------------------
330358
-- | Sends successful event
331359
setSuccess
332360
:: Bool
333-
-> Adaptor app ()
361+
-> Adaptor app r ()
334362
setSuccess = setField "success"
335363
----------------------------------------------------------------------------
336364
setBody
337365
:: ToJSON value
338366
=> value
339-
-> Adaptor app ()
367+
-> Adaptor app r ()
340368
setBody value = setField "body" value
341369
----------------------------------------------------------------------------
342370
setType
343371
:: MessageType
344-
-> Adaptor app ()
372+
-> Adaptor app r ()
345373
setType messageType = do
346374
modify' $ \adaptorState ->
347375
adaptorState
@@ -350,14 +378,14 @@ setType messageType = do
350378
----------------------------------------------------------------------------
351379
setEvent
352380
:: EventType
353-
-> Adaptor app ()
381+
-> Adaptor app r ()
354382
setEvent = setField "event"
355383
----------------------------------------------------------------------------
356384
setField
357385
:: ToJSON value
358386
=> Key
359387
-> value
360-
-> Adaptor app ()
388+
-> Adaptor app r ()
361389
setField key value = do
362390
currentPayload <- gets payload
363391
modify' $ \adaptorState ->
@@ -367,18 +395,18 @@ setField key value = do
367395
----------------------------------------------------------------------------
368396
withConnectionLock
369397
:: IO ()
370-
-> Adaptor app ()
398+
-> Adaptor app r ()
371399
withConnectionLock action = do
372-
lock <- gets handleLock
400+
lock <- asks handleLock
373401
liftIO (withLock lock action)
374402
----------------------------------------------------------------------------
375403
-- | Attempt to parse arguments from the Request
376404
----------------------------------------------------------------------------
377405
getArguments
378406
:: (Show value, FromJSON value)
379-
=> Adaptor app value
407+
=> Adaptor app Request value
380408
getArguments = do
381-
maybeArgs <- gets (args . request)
409+
maybeArgs <- asks (args . request)
382410
let msg = "No args found for this message"
383411
case maybeArgs of
384412
Nothing -> do
@@ -393,15 +421,16 @@ getArguments = do
393421

394422
----------------------------------------------------------------------------
395423
-- | Evaluates Adaptor action by using and updating the state in the MVar
396-
runAdaptorWith :: MVar (AdaptorState app) -> Adaptor app () -> IO ()
397-
runAdaptorWith adaptorStateMVar action = do
398-
modifyMVar_ adaptorStateMVar (flip runAdaptor (resetAdaptorStatePayload >> action))
424+
runAdaptorWith :: AdaptorLocal app r -> AdaptorState -> String -> Adaptor app r () -> IO ()
425+
runAdaptorWith lcl st s (Adaptor action) = do
426+
runStateT (runReaderT (runExceptT action) lcl) st
427+
return ()
399428

400429
----------------------------------------------------------------------------
401430
-- | Utility for evaluating a monad transformer stack
402-
runAdaptor :: AdaptorState app -> Adaptor app () -> IO (AdaptorState app)
403-
runAdaptor adaptorState (Adaptor client) =
404-
runStateT (runExceptT client) adaptorState >>= \case
405-
(Left (errorMessage, maybeMessage), nextState) ->
406-
runAdaptor nextState (sendErrorResponse errorMessage maybeMessage)
407-
(Right (), nextState) -> pure nextState
431+
runAdaptor :: AdaptorLocal app Request -> AdaptorState -> Adaptor app Request () -> IO ()
432+
runAdaptor lcl s (Adaptor client) =
433+
runStateT (runReaderT (runExceptT client) lcl) s >>= \case
434+
(Left (errorMessage, maybeMessage), s') ->
435+
runAdaptor lcl s' (sendErrorResponse errorMessage maybeMessage)
436+
(Right (), s') -> pure ()

0 commit comments

Comments
 (0)