Skip to content

Commit 06134d5

Browse files
authored
Update registerDebugSession event handler thread to take callback function. (#9)
- Relocate 'runAdaptorWith' to Adaptor.hs - Add some comments for 'registerDebugSession'
1 parent 7e4cdbb commit 06134d5

File tree

3 files changed

+41
-25
lines changed

3 files changed

+41
-25
lines changed

dap/exe/Main.hs

Lines changed: 4 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -134,18 +134,17 @@ initESTG AttachArgs {..} = do
134134
, fullPakPath = program
135135
, breakpointMap = mempty
136136
}
137-
adaptorStateMVar <- gets adaptorStateMVar
138137
flip catch handleDebuggerExceptions
139138
$ registerNewDebugSession __sessionId estg
140139
(loadAndRunProgram True True program [] dbgChan DbgStepByStep False defaultDebugSettings)
141-
(handleDebugEvents dbgChan adaptorStateMVar)
140+
(handleDebugEvents dbgChan)
142141

143142
----------------------------------------------------------------------------
144143
-- | Debug Event Handler
145-
handleDebugEvents :: DebuggerChan -> MVar (AdaptorState ESTG) -> IO ()
146-
handleDebugEvents DebuggerChan{..} adaptorStateMVar = forever $ do
144+
handleDebugEvents :: DebuggerChan -> (Adaptor ESTG () -> IO ()) -> IO ()
145+
handleDebugEvents DebuggerChan{..} withAdaptor = forever $ do
147146
dbgEvent <- liftIO (Unagi.readChan dbgAsyncEventOut)
148-
runAdaptorWith adaptorStateMVar $ do
147+
withAdaptor $ do
149148
ESTG {..} <- getDebugSession
150149
let sendEvent ev = sendSuccesfulEvent ev . setBody
151150
case dbgEvent of

dap/src/DAP/Adaptor.hs

Lines changed: 37 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -73,15 +73,21 @@ module DAP.Adaptor
7373
-- * Internal use
7474
, send
7575
, sendRaw
76+
-- * Internal function used to execute actions on behalf of the DAP server
77+
-- from child threads (useful for handling asynchronous debugger events).
78+
, runAdaptorWith
7679
) where
7780
----------------------------------------------------------------------------
7881
import Control.Concurrent ( ThreadId )
82+
import Control.Concurrent.MVar ( newMVar, newEmptyMVar, modifyMVar_
83+
, takeMVar, putMVar, readMVar, MVar )
7984
import Control.Concurrent.Lifted ( fork, killThread )
8085
import Control.Exception ( throwIO )
8186
import Control.Concurrent.STM ( atomically, readTVarIO, modifyTVar' )
8287
import Control.Monad ( when, unless )
83-
import Control.Monad.Except ( throwError )
84-
import Control.Monad.State.Strict ( MonadIO(liftIO), gets, modify', put )
88+
import Control.Monad.Except ( runExceptT, throwError )
89+
import Control.Monad.State ( evalStateT, runStateT, execStateT, gets
90+
, MonadIO(liftIO), gets, modify', put )
8591
import Data.Aeson ( FromJSON, Result (..), fromJSON )
8692
import Data.Maybe ( fromMaybe )
8793
import Data.Aeson.Encode.Pretty ( encodePretty )
@@ -183,18 +189,30 @@ registerNewDebugSession
183189
-> app
184190
-> IO ()
185191
-- ^ Action to run debugger (operates in a forked thread that gets killed when disconnect is set)
186-
-> IO ()
192+
-> ((Adaptor app () -> IO ()) -> IO ())
187193
-- ^ Long running operation, meant to be used as a sink for
188194
-- the debugger to emit events and for the adaptor to forward to the editor
189195
-- This function should be in a 'forever' loop waiting on the read end of
190196
-- a debugger channel.
197+
--
198+
-- This event handler thread also takes an argument that allows any child thread to execute
199+
-- events on behalf of the DAP server (in 'Adaptor app ()'). This function should always be
200+
-- used when sending events to the editor from the debugger (or from any forked thread).
201+
--
202+
-- >
203+
-- > registerNewDebugSession sessionId appState loadDebugger $ \withAdaptor ->
204+
-- > forever $ getDebuggerOutput >>= \output -> do
205+
-- > withAdaptor $ sendOutputEvent defaultOutputEvent { outputEventOutput = output }
206+
-- >
207+
--
191208
-> Adaptor app ()
192209
registerNewDebugSession k v debuggerExecution outputEventSink = do
193210
store <- gets appStore
211+
adaptorStateMVar <- gets adaptorStateMVar
194212
debuggerThreadState <- liftIO $
195213
DebuggerThreadState
196214
<$> fork debuggerExecution
197-
<*> fork outputEventSink
215+
<*> fork (outputEventSink (runAdaptorWith adaptorStateMVar))
198216
liftIO . atomically $ modifyTVar' store (H.insert k (debuggerThreadState, v))
199217
setDebugSessionId k
200218
logInfo $ BL8.pack $ "Registered new debug session: " <> unpack k
@@ -539,3 +557,18 @@ addSourcePathBySourceReferenceId path sourceId =
539557
modify' $ \s -> s
540558
{ sourceReferencesMap = I.insert sourceId path (sourceReferencesMap s)
541559
}
560+
561+
----------------------------------------------------------------------------
562+
-- | Evaluates Adaptor action by using and updating the state in the MVar
563+
runAdaptorWith :: MVar (AdaptorState app) -> Adaptor app () -> IO ()
564+
runAdaptorWith adaptorStateMVar action = do
565+
modifyMVar_ adaptorStateMVar (flip runAdaptor action)
566+
567+
----------------------------------------------------------------------------
568+
-- | Utility for evaluating a monad transformer stack
569+
runAdaptor :: AdaptorState app -> Adaptor app () -> IO (AdaptorState app)
570+
runAdaptor adaptorState (Adaptor client) =
571+
runStateT (runExceptT client) adaptorState >>= \case
572+
(Left (errorMessage, maybeMessage), nextState) ->
573+
runAdaptor nextState (sendErrorResponse errorMessage maybeMessage)
574+
(Right (), nextState) -> pure nextState

dap/src/DAP/Server.hs

Lines changed: 0 additions & 16 deletions
Original file line numberDiff line numberDiff line change
@@ -19,7 +19,6 @@
1919
----------------------------------------------------------------------------
2020
module DAP.Server
2121
( runDAPServer
22-
, runAdaptorWith
2322
) where
2423
----------------------------------------------------------------------------
2524
import Control.Concurrent.MVar ( MVar )
@@ -132,21 +131,6 @@ serviceClient communicate adaptorStateMVar = do
132131
-- loop: serve the next request
133132
serviceClient communicate adaptorStateMVar
134133

135-
----------------------------------------------------------------------------
136-
-- | Evaluates Adaptor action by using and updating the state in the MVar
137-
runAdaptorWith :: MVar (AdaptorState app) -> Adaptor app () -> IO ()
138-
runAdaptorWith adaptorStateMVar action = do
139-
modifyMVar_ adaptorStateMVar (flip runAdaptor action)
140-
141-
----------------------------------------------------------------------------
142-
-- | Utility for evaluating a monad transformer stack
143-
runAdaptor :: AdaptorState app -> Adaptor app () -> IO (AdaptorState app)
144-
runAdaptor adaptorState (Adaptor client) =
145-
runStateT (runExceptT client) adaptorState >>= \case
146-
(Left (errorMessage, maybeMessage), nextState) ->
147-
runAdaptor nextState (sendErrorResponse errorMessage maybeMessage)
148-
(Right (), nextState) -> pure nextState
149-
150134
----------------------------------------------------------------------------
151135
-- | Handle exceptions from client threads, parse and log accordingly
152136
exceptionHandler :: Handle -> SockAddr -> SomeException -> IO ()

0 commit comments

Comments
 (0)