@@ -50,15 +50,16 @@ module DAP.Adaptor
50
50
-- * Internal function used to execute actions on behalf of the DAP server
51
51
-- from child threads (useful for handling asynchronous debugger events).
52
52
, runAdaptorWith
53
+ , runAdaptor
53
54
) where
54
55
----------------------------------------------------------------------------
55
- import Control.Concurrent.MVar ( modifyMVar_ , MVar )
56
56
import Control.Concurrent.Lifted ( fork , killThread )
57
57
import Control.Exception ( throwIO )
58
58
import Control.Concurrent.STM ( atomically , readTVarIO , modifyTVar' )
59
59
import Control.Monad ( when , unless )
60
60
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
62
63
import Data.Aeson ( FromJSON , Result (.. ), fromJSON )
63
64
import Data.Aeson.Encode.Pretty ( encodePretty )
64
65
import Data.Aeson.Types ( object , Key , KeyValue ((.=) ), ToJSON )
@@ -68,23 +69,24 @@ import System.IO ( Handle )
68
69
import qualified Data.ByteString.Lazy.Char8 as BL8
69
70
import qualified Data.ByteString.Char8 as BS
70
71
import qualified Data.HashMap.Strict as H
72
+ import Data.IORef
71
73
----------------------------------------------------------------------------
72
74
import DAP.Types
73
75
import DAP.Utils
74
76
import DAP.Internal
75
77
----------------------------------------------------------------------------
76
- logWarn :: BL8. ByteString -> Adaptor app ()
78
+ logWarn :: BL8. ByteString -> Adaptor app r ()
77
79
logWarn msg = logWithAddr WARN Nothing (withBraces msg)
78
80
----------------------------------------------------------------------------
79
- logError :: BL8. ByteString -> Adaptor app ()
81
+ logError :: BL8. ByteString -> Adaptor app r ()
80
82
logError msg = logWithAddr ERROR Nothing (withBraces msg)
81
83
----------------------------------------------------------------------------
82
- logInfo :: BL8. ByteString -> Adaptor app ()
84
+ logInfo :: BL8. ByteString -> Adaptor app r ()
83
85
logInfo msg = logWithAddr INFO Nothing (withBraces msg)
84
86
----------------------------------------------------------------------------
85
87
-- | Meant for internal consumption, used to signify a message has been
86
88
-- SENT from the server
87
- debugMessage :: BL8. ByteString -> Adaptor app ()
89
+ debugMessage :: BL8. ByteString -> Adaptor app r ()
88
90
debugMessage msg = do
89
91
shouldLog <- getDebugLogging
90
92
addr <- getAddress
@@ -93,7 +95,7 @@ debugMessage msg = do
93
95
$ logger DEBUG addr (Just SENT ) msg
94
96
----------------------------------------------------------------------------
95
97
-- | Meant for external consumption
96
- logWithAddr :: Level -> Maybe DebugStatus -> BL8. ByteString -> Adaptor app ()
98
+ logWithAddr :: Level -> Maybe DebugStatus -> BL8. ByteString -> Adaptor app r ()
97
99
logWithAddr level status msg = do
98
100
addr <- getAddress
99
101
liftIO (logger level addr status msg)
@@ -113,38 +115,42 @@ logger level addr maybeDebug msg = do
113
115
, msg
114
116
]
115
117
----------------------------------------------------------------------------
116
- getDebugLogging :: Adaptor app Bool
117
- getDebugLogging = gets (debugLogging . serverConfig)
118
+ getDebugLogging :: Adaptor app r Bool
119
+ getDebugLogging = asks (debugLogging . serverConfig)
118
120
----------------------------------------------------------------------------
119
- getServerCapabilities :: Adaptor app Capabilities
120
- getServerCapabilities = gets (serverCapabilities . serverConfig)
121
+ getServerCapabilities :: Adaptor app r Capabilities
122
+ getServerCapabilities = asks (serverCapabilities . serverConfig)
121
123
----------------------------------------------------------------------------
122
- getAddress :: Adaptor app SockAddr
123
- getAddress = gets address
124
+ getAddress :: Adaptor app r SockAddr
125
+ getAddress = asks address
124
126
----------------------------------------------------------------------------
125
- getHandle :: Adaptor app Handle
126
- getHandle = gets handle
127
+ getHandle :: Adaptor app r Handle
128
+ getHandle = asks handle
127
129
----------------------------------------------------------------------------
128
- getRequestSeqNum :: Adaptor app Seq
129
- getRequestSeqNum = gets (requestSeqNum . request)
130
+ getRequestSeqNum :: Adaptor app Request Seq
131
+ getRequestSeqNum = asks (requestSeqNum . request)
130
132
----------------------------------------------------------------------------
131
- getDebugSessionId :: Adaptor app SessionId
133
+ getDebugSessionId :: Adaptor app r SessionId
132
134
getDebugSessionId = do
133
- gets sessionId >>= \ case
135
+ var <- asks (sessionId)
136
+ res <- liftIO $ readIORef var
137
+ case res of
134
138
Nothing -> sessionNotFound
135
139
Just sessionId -> pure sessionId
136
140
where
137
141
sessionNotFound = do
138
142
let err = " No Debug Session has started"
139
143
sendError (ErrorMessage (pack err)) Nothing
140
144
----------------------------------------------------------------------------
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)
143
149
----------------------------------------------------------------------------
144
150
registerNewDebugSession
145
151
:: SessionId
146
152
-> app
147
- -> [(( Adaptor app () -> IO () ) -> IO () )]
153
+ -> [(Adaptor app () () -> IO () ) -> IO () ]
148
154
-- ^ Actions to run debugger (operates in a forked thread that gets killed when disconnect is set)
149
155
-- Long running operation, meant to be used as a sink for
150
156
-- the debugger to emit events and for the adaptor to forward to the editor
@@ -161,29 +167,32 @@ registerNewDebugSession
161
167
-- > withAdaptor $ sendOutputEvent defaultOutputEvent { outputEventOutput = output }
162
168
-- > ]
163
169
--
164
- -> Adaptor app ()
170
+ -> Adaptor app r ()
165
171
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 []
168
176
debuggerThreadState <- liftIO $
169
177
DebuggerThreadState
170
- <$> sequence [fork $ action (runAdaptorWith adaptorStateMVar ) | action <- debuggerConcurrentActions]
178
+ <$> sequence [fork $ action (runAdaptorWith lcl' emptyState " s " ) | action <- debuggerConcurrentActions]
171
179
liftIO . atomically $ modifyTVar' store (H. insert k (debuggerThreadState, v))
172
- setDebugSessionId k
173
180
logInfo $ BL8. pack $ " Registered new debug session: " <> unpack k
181
+ setDebugSessionId k
182
+
174
183
----------------------------------------------------------------------------
175
- updateDebugSession :: (app -> app ) -> Adaptor app ()
184
+ updateDebugSession :: (app -> app ) -> Adaptor app r ()
176
185
updateDebugSession updateFun = do
177
186
sessionId <- getDebugSessionId
178
- store <- gets appStore
187
+ store <- asks appStore
179
188
liftIO . atomically $ modifyTVar' store (H. adjust (fmap updateFun) sessionId)
180
189
----------------------------------------------------------------------------
181
- getDebugSession :: Adaptor a a
190
+ getDebugSession :: Adaptor a r a
182
191
getDebugSession = do
183
192
(_, _, app) <- getDebugSessionWithThreadIdAndSessionId
184
193
pure app
185
194
----------------------------------------------------------------------------
186
- getDebugSessionWithThreadIdAndSessionId :: Adaptor app (SessionId , DebuggerThreadState , app )
195
+ getDebugSessionWithThreadIdAndSessionId :: Adaptor app r (SessionId , DebuggerThreadState , app )
187
196
getDebugSessionWithThreadIdAndSessionId = do
188
197
sessionId <- getDebugSessionId
189
198
appStore <- liftIO . readTVarIO =<< getAppStore
@@ -203,7 +212,7 @@ getDebugSessionWithThreadIdAndSessionId = do
203
212
-- | Whenever a debug Session ends (cleanly or otherwise) this function
204
213
-- will remove the local debugger communication state from the global state
205
214
----------------------------------------------------------------------------
206
- destroyDebugSession :: Adaptor app ()
215
+ destroyDebugSession :: Adaptor app r ()
207
216
destroyDebugSession = do
208
217
(sessionId, DebuggerThreadState {.. }, _) <- getDebugSessionWithThreadIdAndSessionId
209
218
store <- getAppStore
@@ -212,17 +221,17 @@ destroyDebugSession = do
212
221
atomically $ modifyTVar' store (H. delete sessionId)
213
222
logInfo $ BL8. pack $ " SessionId " <> unpack sessionId <> " ended"
214
223
----------------------------------------------------------------------------
215
- getAppStore :: Adaptor app (AppStore app )
216
- getAppStore = gets appStore
224
+ getAppStore :: Adaptor app r (AppStore app )
225
+ getAppStore = asks appStore
217
226
----------------------------------------------------------------------------
218
- getCommand :: Adaptor app Command
219
- getCommand = command <$> gets request
227
+ getCommand :: Adaptor app Request Command
228
+ getCommand = command <$> asks request
220
229
----------------------------------------------------------------------------
221
230
-- | 'sendRaw' (internal use only)
222
231
-- Sends a raw JSON payload to the editor. No "seq", "type" or "command" fields are set.
223
232
-- The message is still encoded with the ProtocolMessage Header, byte count, and CRLF.
224
233
--
225
- sendRaw :: ToJSON value => value -> Adaptor app ()
234
+ sendRaw :: ToJSON value => value -> Adaptor app r ()
226
235
sendRaw value = do
227
236
handle <- getHandle
228
237
address <- getAddress
@@ -234,7 +243,7 @@ sendRaw value = do
234
243
-- i.e. "request_seq" and "command".
235
244
-- We also have to be sure to reset the message payload
236
245
----------------------------------------------------------------------------
237
- send :: Adaptor app () -> Adaptor app ()
246
+ send :: Adaptor app Request () -> Adaptor app Request ()
238
247
send action = do
239
248
() <- action
240
249
cmd <- getCommand
@@ -258,9 +267,28 @@ send action = do
258
267
259
268
-- Send payload to client from debug adaptor
260
269
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
261
284
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
263
289
resetAdaptorStatePayload
290
+
291
+
264
292
----------------------------------------------------------------------------
265
293
-- | Writes payload to the given 'Handle' using the local connection lock
266
294
----------------------------------------------------------------------------
@@ -269,31 +297,31 @@ writeToHandle
269
297
=> SockAddr
270
298
-> Handle
271
299
-> event
272
- -> Adaptor app ()
300
+ -> Adaptor app r ()
273
301
writeToHandle _ handle evt = do
274
302
let msg = encodeBaseProtocolMessage evt
275
303
debugMessage (" \n " <> encodePretty evt)
276
304
withConnectionLock (BS. hPutStr handle msg)
277
305
----------------------------------------------------------------------------
278
306
-- | Resets Adaptor's payload
279
307
----------------------------------------------------------------------------
280
- resetAdaptorStatePayload :: Adaptor app ()
308
+ resetAdaptorStatePayload :: Adaptor app r ()
281
309
resetAdaptorStatePayload = modify' $ \ s -> s { payload = [] }
282
310
----------------------------------------------------------------------------
283
- sendSuccesfulResponse :: Adaptor app () -> Adaptor app ()
311
+ sendSuccesfulResponse :: Adaptor app Request () -> Adaptor app Request ()
284
312
sendSuccesfulResponse action = do
285
313
send $ do
286
314
setType MessageTypeResponse
287
315
setSuccess True
288
316
action
289
317
----------------------------------------------------------------------------
290
- sendSuccesfulEmptyResponse :: Adaptor app ()
318
+ sendSuccesfulEmptyResponse :: Adaptor app Request ()
291
319
sendSuccesfulEmptyResponse = sendSuccesfulResponse (pure () )
292
320
----------------------------------------------------------------------------
293
321
-- | Sends successful event
294
- sendSuccesfulEvent :: EventType -> Adaptor app () -> Adaptor app ()
322
+ sendSuccesfulEvent :: EventType -> Adaptor app r () -> Adaptor app r ()
295
323
sendSuccesfulEvent event action = do
296
- send $ do
324
+ sendEvent $ do
297
325
setEvent event
298
326
setType MessageTypeEvent
299
327
action
@@ -305,7 +333,7 @@ sendSuccesfulEvent event action = do
305
333
sendError
306
334
:: ErrorMessage
307
335
-> Maybe Message
308
- -> Adaptor app a
336
+ -> Adaptor app r a
309
337
sendError errorMessage maybeMessage = do
310
338
throwError (errorMessage, maybeMessage)
311
339
----------------------------------------------------------------------------
@@ -314,7 +342,7 @@ sendError errorMessage maybeMessage = do
314
342
sendErrorResponse
315
343
:: ErrorMessage
316
344
-> Maybe Message
317
- -> Adaptor app ()
345
+ -> Adaptor app Request ()
318
346
sendErrorResponse errorMessage maybeMessage = do
319
347
send $ do
320
348
setType MessageTypeResponse
@@ -324,24 +352,24 @@ sendErrorResponse errorMessage maybeMessage = do
324
352
----------------------------------------------------------------------------
325
353
setErrorMessage
326
354
:: ErrorMessage
327
- -> Adaptor app ()
355
+ -> Adaptor app r ()
328
356
setErrorMessage v = setField " message" v
329
357
----------------------------------------------------------------------------
330
358
-- | Sends successful event
331
359
setSuccess
332
360
:: Bool
333
- -> Adaptor app ()
361
+ -> Adaptor app r ()
334
362
setSuccess = setField " success"
335
363
----------------------------------------------------------------------------
336
364
setBody
337
365
:: ToJSON value
338
366
=> value
339
- -> Adaptor app ()
367
+ -> Adaptor app r ()
340
368
setBody value = setField " body" value
341
369
----------------------------------------------------------------------------
342
370
setType
343
371
:: MessageType
344
- -> Adaptor app ()
372
+ -> Adaptor app r ()
345
373
setType messageType = do
346
374
modify' $ \ adaptorState ->
347
375
adaptorState
@@ -350,14 +378,14 @@ setType messageType = do
350
378
----------------------------------------------------------------------------
351
379
setEvent
352
380
:: EventType
353
- -> Adaptor app ()
381
+ -> Adaptor app r ()
354
382
setEvent = setField " event"
355
383
----------------------------------------------------------------------------
356
384
setField
357
385
:: ToJSON value
358
386
=> Key
359
387
-> value
360
- -> Adaptor app ()
388
+ -> Adaptor app r ()
361
389
setField key value = do
362
390
currentPayload <- gets payload
363
391
modify' $ \ adaptorState ->
@@ -367,18 +395,18 @@ setField key value = do
367
395
----------------------------------------------------------------------------
368
396
withConnectionLock
369
397
:: IO ()
370
- -> Adaptor app ()
398
+ -> Adaptor app r ()
371
399
withConnectionLock action = do
372
- lock <- gets handleLock
400
+ lock <- asks handleLock
373
401
liftIO (withLock lock action)
374
402
----------------------------------------------------------------------------
375
403
-- | Attempt to parse arguments from the Request
376
404
----------------------------------------------------------------------------
377
405
getArguments
378
406
:: (Show value , FromJSON value )
379
- => Adaptor app value
407
+ => Adaptor app Request value
380
408
getArguments = do
381
- maybeArgs <- gets (args . request)
409
+ maybeArgs <- asks (args . request)
382
410
let msg = " No args found for this message"
383
411
case maybeArgs of
384
412
Nothing -> do
@@ -393,15 +421,16 @@ getArguments = do
393
421
394
422
----------------------------------------------------------------------------
395
423
-- | 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 ()
399
428
400
429
----------------------------------------------------------------------------
401
430
-- | 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