@@ -59,6 +59,7 @@ import Control.Concurrent.STM ( atomically, readTVarIO, modifyTVar
5959import Control.Monad ( when , unless )
6060import Control.Monad.Except ( runExceptT , throwError )
6161import Control.Monad.State ( runStateT , gets , MonadIO (liftIO ), gets , modify' )
62+ import Control.Monad.Reader
6263import Data.Aeson ( FromJSON , Result (.. ), fromJSON )
6364import Data.Aeson.Encode.Pretty ( encodePretty )
6465import Data.Aeson.Types ( object , Key , KeyValue ((.=) ), ToJSON )
@@ -68,23 +69,25 @@ import System.IO ( Handle )
6869import qualified Data.ByteString.Lazy.Char8 as BL8
6970import qualified Data.ByteString.Char8 as BS
7071import qualified Data.HashMap.Strict as H
72+ import GHC.Stack
73+ import Data.IORef
7174----------------------------------------------------------------------------
7275import DAP.Types
7376import DAP.Utils
7477import DAP.Internal
7578----------------------------------------------------------------------------
76- logWarn :: BL8. ByteString -> Adaptor app ()
79+ logWarn :: BL8. ByteString -> Adaptor app r ()
7780logWarn msg = logWithAddr WARN Nothing (withBraces msg)
7881----------------------------------------------------------------------------
79- logError :: BL8. ByteString -> Adaptor app ()
82+ logError :: BL8. ByteString -> Adaptor app r ()
8083logError msg = logWithAddr ERROR Nothing (withBraces msg)
8184----------------------------------------------------------------------------
82- logInfo :: BL8. ByteString -> Adaptor app ()
85+ logInfo :: BL8. ByteString -> Adaptor app r ()
8386logInfo msg = logWithAddr INFO Nothing (withBraces msg)
8487----------------------------------------------------------------------------
8588-- | Meant for internal consumption, used to signify a message has been
8689-- SENT from the server
87- debugMessage :: BL8. ByteString -> Adaptor app ()
90+ debugMessage :: BL8. ByteString -> Adaptor app r ()
8891debugMessage msg = do
8992 shouldLog <- getDebugLogging
9093 addr <- getAddress
@@ -93,7 +96,7 @@ debugMessage msg = do
9396 $ logger DEBUG addr (Just SENT ) msg
9497----------------------------------------------------------------------------
9598-- | Meant for external consumption
96- logWithAddr :: Level -> Maybe DebugStatus -> BL8. ByteString -> Adaptor app ()
99+ logWithAddr :: Level -> Maybe DebugStatus -> BL8. ByteString -> Adaptor app r ()
97100logWithAddr level status msg = do
98101 addr <- getAddress
99102 liftIO (logger level addr status msg)
@@ -113,38 +116,42 @@ logger level addr maybeDebug msg = do
113116 , msg
114117 ]
115118----------------------------------------------------------------------------
116- getDebugLogging :: Adaptor app Bool
117- getDebugLogging = gets (debugLogging . serverConfig)
119+ getDebugLogging :: Adaptor app r Bool
120+ getDebugLogging = asks (debugLogging . serverConfig)
118121----------------------------------------------------------------------------
119- getServerCapabilities :: Adaptor app Capabilities
120- getServerCapabilities = gets (serverCapabilities . serverConfig)
122+ getServerCapabilities :: Adaptor app r Capabilities
123+ getServerCapabilities = asks (serverCapabilities . serverConfig)
121124----------------------------------------------------------------------------
122- getAddress :: Adaptor app SockAddr
123- getAddress = gets address
125+ getAddress :: Adaptor app r SockAddr
126+ getAddress = asks address
124127----------------------------------------------------------------------------
125- getHandle :: Adaptor app Handle
126- getHandle = gets handle
128+ getHandle :: Adaptor app r Handle
129+ getHandle = asks handle
127130----------------------------------------------------------------------------
128- getRequestSeqNum :: Adaptor app Seq
129- getRequestSeqNum = gets (requestSeqNum . request)
131+ getRequestSeqNum :: Adaptor app Request Seq
132+ getRequestSeqNum = asks (requestSeqNum . request)
130133----------------------------------------------------------------------------
131- getDebugSessionId :: Adaptor app SessionId
134+ getDebugSessionId :: Adaptor app r SessionId
132135getDebugSessionId = do
133- gets sessionId >>= \ case
136+ var <- asks (sessionId)
137+ res <- liftIO $ readIORef var
138+ case res of
134139 Nothing -> sessionNotFound
135140 Just sessionId -> pure sessionId
136141 where
137142 sessionNotFound = do
138143 let err = " No Debug Session has started"
139144 sendError (ErrorMessage (pack err)) Nothing
140145----------------------------------------------------------------------------
141- setDebugSessionId :: SessionId -> Adaptor app ()
142- setDebugSessionId session = modify' $ \ s -> s { sessionId = Just session }
146+ setDebugSessionId :: SessionId -> Adaptor app r ()
147+ setDebugSessionId session = do
148+ var <- asks sessionId
149+ liftIO $ writeIORef var (Just session)
143150----------------------------------------------------------------------------
144151registerNewDebugSession
145152 :: SessionId
146153 -> app
147- -> [(( Adaptor app () -> IO () ) -> IO () )]
154+ -> [(Adaptor app () () -> IO () ) -> IO () ]
148155 -- ^ Actions to run debugger (operates in a forked thread that gets killed when disconnect is set)
149156 -- Long running operation, meant to be used as a sink for
150157 -- the debugger to emit events and for the adaptor to forward to the editor
@@ -161,29 +168,32 @@ registerNewDebugSession
161168 -- > withAdaptor $ sendOutputEvent defaultOutputEvent { outputEventOutput = output }
162169 -- > ]
163170 --
164- -> Adaptor app ()
171+ -> Adaptor app r ()
165172registerNewDebugSession k v debuggerConcurrentActions = do
166- store <- gets appStore
167- adaptorStateMVar <- gets adaptorStateMVar
173+ store <- asks appStore
174+ lcl <- ask
175+ let lcl' = lcl { request = () }
176+ let emptyState = AdaptorState MessageTypeEvent []
168177 debuggerThreadState <- liftIO $
169178 DebuggerThreadState
170- <$> sequence [fork $ action (runAdaptorWith adaptorStateMVar ) | action <- debuggerConcurrentActions]
179+ <$> sequence [fork $ action (runAdaptorWith lcl' emptyState " s " ) | action <- debuggerConcurrentActions]
171180 liftIO . atomically $ modifyTVar' store (H. insert k (debuggerThreadState, v))
172- setDebugSessionId k
173181 logInfo $ BL8. pack $ " Registered new debug session: " <> unpack k
182+ setDebugSessionId k
183+
174184----------------------------------------------------------------------------
175- updateDebugSession :: (app -> app ) -> Adaptor app ()
185+ updateDebugSession :: (app -> app ) -> Adaptor app r ()
176186updateDebugSession updateFun = do
177187 sessionId <- getDebugSessionId
178- store <- gets appStore
188+ store <- asks appStore
179189 liftIO . atomically $ modifyTVar' store (H. adjust (fmap updateFun) sessionId)
180190----------------------------------------------------------------------------
181- getDebugSession :: Adaptor a a
191+ getDebugSession :: Adaptor a r a
182192getDebugSession = do
183193 (_, _, app) <- getDebugSessionWithThreadIdAndSessionId
184194 pure app
185195----------------------------------------------------------------------------
186- getDebugSessionWithThreadIdAndSessionId :: Adaptor app (SessionId , DebuggerThreadState , app )
196+ getDebugSessionWithThreadIdAndSessionId :: Adaptor app r (SessionId , DebuggerThreadState , app )
187197getDebugSessionWithThreadIdAndSessionId = do
188198 sessionId <- getDebugSessionId
189199 appStore <- liftIO . readTVarIO =<< getAppStore
@@ -203,7 +213,7 @@ getDebugSessionWithThreadIdAndSessionId = do
203213-- | Whenever a debug Session ends (cleanly or otherwise) this function
204214-- will remove the local debugger communication state from the global state
205215----------------------------------------------------------------------------
206- destroyDebugSession :: Adaptor app ()
216+ destroyDebugSession :: Adaptor app r ()
207217destroyDebugSession = do
208218 (sessionId, DebuggerThreadState {.. }, _) <- getDebugSessionWithThreadIdAndSessionId
209219 store <- getAppStore
@@ -212,17 +222,17 @@ destroyDebugSession = do
212222 atomically $ modifyTVar' store (H. delete sessionId)
213223 logInfo $ BL8. pack $ " SessionId " <> unpack sessionId <> " ended"
214224----------------------------------------------------------------------------
215- getAppStore :: Adaptor app (AppStore app )
216- getAppStore = gets appStore
225+ getAppStore :: Adaptor app r (AppStore app )
226+ getAppStore = asks appStore
217227----------------------------------------------------------------------------
218- getCommand :: Adaptor app Command
219- getCommand = command <$> gets request
228+ getCommand :: Adaptor app Request Command
229+ getCommand = command <$> asks request
220230----------------------------------------------------------------------------
221231-- | 'sendRaw' (internal use only)
222232-- Sends a raw JSON payload to the editor. No "seq", "type" or "command" fields are set.
223233-- The message is still encoded with the ProtocolMessage Header, byte count, and CRLF.
224234--
225- sendRaw :: ToJSON value => value -> Adaptor app ()
235+ sendRaw :: ToJSON value => value -> Adaptor app r ()
226236sendRaw value = do
227237 handle <- getHandle
228238 address <- getAddress
@@ -234,7 +244,7 @@ sendRaw value = do
234244-- i.e. "request_seq" and "command".
235245-- We also have to be sure to reset the message payload
236246----------------------------------------------------------------------------
237- send :: Adaptor app () -> Adaptor app ()
247+ send :: Adaptor app Request () -> Adaptor app Request ()
238248send action = do
239249 () <- action
240250 cmd <- getCommand
@@ -258,9 +268,28 @@ send action = do
258268
259269 -- Send payload to client from debug adaptor
260270 writeToHandle address handle payload
271+ resetAdaptorStatePayload
272+
273+ sendEvent :: Adaptor app r () -> Adaptor app r ()
274+ sendEvent action = do
275+ () <- action
276+ handle <- getHandle
277+ messageType <- gets messageType
278+ address <- getAddress
279+ case messageType of
280+ MessageTypeResponse -> error " use send"
281+ MessageTypeRequest -> error " use send"
282+ MessageTypeEvent -> do
283+ address <- getAddress
284+ setField " type" messageType
261285
262- -- Reset payload each time a send occurs
286+ -- Once all fields are set, fetch the payload for sending
287+ payload <- object <$> gets payload
288+ -- Send payload to client from debug adaptor
289+ writeToHandle address handle payload
263290 resetAdaptorStatePayload
291+
292+
264293----------------------------------------------------------------------------
265294-- | Writes payload to the given 'Handle' using the local connection lock
266295----------------------------------------------------------------------------
@@ -269,31 +298,31 @@ writeToHandle
269298 => SockAddr
270299 -> Handle
271300 -> event
272- -> Adaptor app ()
301+ -> Adaptor app r ()
273302writeToHandle _ handle evt = do
274303 let msg = encodeBaseProtocolMessage evt
275304 debugMessage (" \n " <> encodePretty evt)
276305 withConnectionLock (BS. hPutStr handle msg)
277306----------------------------------------------------------------------------
278307-- | Resets Adaptor's payload
279308----------------------------------------------------------------------------
280- resetAdaptorStatePayload :: Adaptor app ()
309+ resetAdaptorStatePayload :: Adaptor app r ()
281310resetAdaptorStatePayload = modify' $ \ s -> s { payload = [] }
282311----------------------------------------------------------------------------
283- sendSuccesfulResponse :: Adaptor app () -> Adaptor app ()
312+ sendSuccesfulResponse :: Adaptor app Request () -> Adaptor app Request ()
284313sendSuccesfulResponse action = do
285314 send $ do
286315 setType MessageTypeResponse
287316 setSuccess True
288317 action
289318----------------------------------------------------------------------------
290- sendSuccesfulEmptyResponse :: Adaptor app ()
319+ sendSuccesfulEmptyResponse :: Adaptor app Request ()
291320sendSuccesfulEmptyResponse = sendSuccesfulResponse (pure () )
292321----------------------------------------------------------------------------
293322-- | Sends successful event
294- sendSuccesfulEvent :: EventType -> Adaptor app () -> Adaptor app ()
323+ sendSuccesfulEvent :: EventType -> Adaptor app r () -> Adaptor app r ()
295324sendSuccesfulEvent event action = do
296- send $ do
325+ sendEvent $ do
297326 setEvent event
298327 setType MessageTypeEvent
299328 action
@@ -305,7 +334,7 @@ sendSuccesfulEvent event action = do
305334sendError
306335 :: ErrorMessage
307336 -> Maybe Message
308- -> Adaptor app a
337+ -> Adaptor app r a
309338sendError errorMessage maybeMessage = do
310339 throwError (errorMessage, maybeMessage)
311340----------------------------------------------------------------------------
@@ -314,7 +343,7 @@ sendError errorMessage maybeMessage = do
314343sendErrorResponse
315344 :: ErrorMessage
316345 -> Maybe Message
317- -> Adaptor app ()
346+ -> Adaptor app Request ()
318347sendErrorResponse errorMessage maybeMessage = do
319348 send $ do
320349 setType MessageTypeResponse
@@ -324,24 +353,24 @@ sendErrorResponse errorMessage maybeMessage = do
324353----------------------------------------------------------------------------
325354setErrorMessage
326355 :: ErrorMessage
327- -> Adaptor app ()
356+ -> Adaptor app r ()
328357setErrorMessage v = setField " message" v
329358----------------------------------------------------------------------------
330359-- | Sends successful event
331360setSuccess
332361 :: Bool
333- -> Adaptor app ()
362+ -> Adaptor app r ()
334363setSuccess = setField " success"
335364----------------------------------------------------------------------------
336365setBody
337366 :: ToJSON value
338367 => value
339- -> Adaptor app ()
368+ -> Adaptor app r ()
340369setBody value = setField " body" value
341370----------------------------------------------------------------------------
342371setType
343372 :: MessageType
344- -> Adaptor app ()
373+ -> Adaptor app r ()
345374setType messageType = do
346375 modify' $ \ adaptorState ->
347376 adaptorState
@@ -350,14 +379,14 @@ setType messageType = do
350379----------------------------------------------------------------------------
351380setEvent
352381 :: EventType
353- -> Adaptor app ()
382+ -> Adaptor app r ()
354383setEvent = setField " event"
355384----------------------------------------------------------------------------
356385setField
357386 :: ToJSON value
358387 => Key
359388 -> value
360- -> Adaptor app ()
389+ -> Adaptor app r ()
361390setField key value = do
362391 currentPayload <- gets payload
363392 modify' $ \ adaptorState ->
@@ -367,18 +396,18 @@ setField key value = do
367396----------------------------------------------------------------------------
368397withConnectionLock
369398 :: IO ()
370- -> Adaptor app ()
399+ -> Adaptor app r ()
371400withConnectionLock action = do
372- lock <- gets handleLock
401+ lock <- asks handleLock
373402 liftIO (withLock lock action)
374403----------------------------------------------------------------------------
375404-- | Attempt to parse arguments from the Request
376405----------------------------------------------------------------------------
377406getArguments
378407 :: (Show value , FromJSON value )
379- => Adaptor app value
408+ => Adaptor app Request value
380409getArguments = do
381- maybeArgs <- gets (args . request)
410+ maybeArgs <- asks (args . request)
382411 let msg = " No args found for this message"
383412 case maybeArgs of
384413 Nothing -> do
@@ -393,15 +422,16 @@ getArguments = do
393422
394423----------------------------------------------------------------------------
395424-- | 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))
425+ runAdaptorWith :: AdaptorLocal app r -> AdaptorState -> String -> Adaptor app r () -> IO ()
426+ runAdaptorWith lcl st s (Adaptor action) = do
427+ runStateT (runReaderT (runExceptT action) lcl) st
428+ return ()
399429
400430----------------------------------------------------------------------------
401431-- | 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
432+ runAdaptor :: AdaptorLocal app Request -> AdaptorState -> Adaptor app Request () -> IO ()
433+ runAdaptor lcl s (Adaptor client) =
434+ runStateT (runReaderT ( runExceptT client) lcl) s >>= \ case
435+ (Left (errorMessage, maybeMessage), s' ) ->
436+ runAdaptor lcl s' (sendErrorResponse errorMessage maybeMessage)
437+ (Right () , s' ) -> pure ()
0 commit comments