{-# LANGUAGE MultiParamTypeClasses #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
module Haskell.Debug.Adapter.State.DebugRun.Continue where
import Control.Monad.IO.Class
import qualified System.Log.Logger as L
import qualified Text.Read as R
import Control.Monad.Except
import qualified Haskell.DAP as DAP
import Haskell.Debug.Adapter.Type
import Haskell.Debug.Adapter.Constant
import qualified Haskell.Debug.Adapter.Utility as U
import qualified Haskell.Debug.Adapter.GHCi as P
import qualified Haskell.Debug.Adapter.State.Utility as SU
instance StateActivityIF DebugRunStateData DAP.ContinueRequest where
action :: AppState DebugRunStateData
-> Request ContinueRequest -> AppContext (Maybe StateTransit)
action AppState DebugRunStateData
_ (ContinueRequest ContinueRequest
req) = do
IO () -> StateT AppStores (ExceptT ErrMsg IO) ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> StateT AppStores (ExceptT ErrMsg IO) ())
-> IO () -> StateT AppStores (ExceptT ErrMsg IO) ()
forall a b. (a -> b) -> a -> b
$ ErrMsg -> ErrMsg -> IO ()
L.debugM ErrMsg
_LOG_APP (ErrMsg -> IO ()) -> ErrMsg -> IO ()
forall a b. (a -> b) -> a -> b
$ ErrMsg
"DebugRunState ContinueRequest called. " ErrMsg -> ErrMsg -> ErrMsg
forall a. [a] -> [a] -> [a]
++ ContinueRequest -> ErrMsg
forall a. Show a => a -> ErrMsg
show ContinueRequest
req
ContinueRequest -> AppContext (Maybe StateTransit)
app ContinueRequest
req
app :: DAP.ContinueRequest -> AppContext (Maybe StateTransit)
app :: ContinueRequest -> AppContext (Maybe StateTransit)
app ContinueRequest
req = (AppContext (Maybe StateTransit)
-> (ErrMsg -> AppContext (Maybe StateTransit))
-> AppContext (Maybe StateTransit))
-> (ErrMsg -> AppContext (Maybe StateTransit))
-> AppContext (Maybe StateTransit)
-> AppContext (Maybe StateTransit)
forall a b c. (a -> b -> c) -> b -> a -> c
flip AppContext (Maybe StateTransit)
-> (ErrMsg -> AppContext (Maybe StateTransit))
-> AppContext (Maybe StateTransit)
forall e (m :: * -> *) a.
MonadError e m =>
m a -> (e -> m a) -> m a
catchError ErrMsg -> AppContext (Maybe StateTransit)
errHdl (AppContext (Maybe StateTransit)
-> AppContext (Maybe StateTransit))
-> AppContext (Maybe StateTransit)
-> AppContext (Maybe StateTransit)
forall a b. (a -> b) -> a -> b
$ do
let args :: ContinueRequestArguments
args = ContinueRequest -> ContinueRequestArguments
DAP.argumentsContinueRequest ContinueRequest
req
dap :: ErrMsg
dap = ErrMsg
":dap-continue "
cmd :: ErrMsg
cmd = ErrMsg
dap ErrMsg -> ErrMsg -> ErrMsg
forall a. [a] -> [a] -> [a]
++ ContinueRequestArguments -> ErrMsg
forall a. Show a => a -> ErrMsg
U.showDAP ContinueRequestArguments
args
dbg :: ErrMsg
dbg = ErrMsg
dap ErrMsg -> ErrMsg -> ErrMsg
forall a. [a] -> [a] -> [a]
++ ContinueRequestArguments -> ErrMsg
forall a. Show a => a -> ErrMsg
show ContinueRequestArguments
args
ErrMsg -> StateT AppStores (ExceptT ErrMsg IO) ()
P.command ErrMsg
cmd
ErrMsg -> ErrMsg -> StateT AppStores (ExceptT ErrMsg IO) ()
U.debugEV ErrMsg
_LOG_APP ErrMsg
dbg
[ErrMsg]
outStr <- AppContext [ErrMsg]
P.expectPmpt
Int
resSeq <- AppContext Int
U.getIncreasedResponseSequence
let res :: ContinueResponse
res = ContinueResponse
DAP.defaultContinueResponse {
seqContinueResponse :: Int
DAP.seqContinueResponse = Int
resSeq
, request_seqContinueResponse :: Int
DAP.request_seqContinueResponse = ContinueRequest -> Int
DAP.seqContinueRequest ContinueRequest
req
, successContinueResponse :: Bool
DAP.successContinueResponse = Bool
True
}
Response -> StateT AppStores (ExceptT ErrMsg IO) ()
U.addResponse (Response -> StateT AppStores (ExceptT ErrMsg IO) ())
-> Response -> StateT AppStores (ExceptT ErrMsg IO) ()
forall a b. (a -> b) -> a -> b
$ ContinueResponse -> Response
ContinueResponse ContinueResponse
res
[ErrMsg] -> AppContext ErrMsg
SU.takeDapResult [ErrMsg]
outStr AppContext ErrMsg
-> (ErrMsg -> StateT AppStores (ExceptT ErrMsg IO) ())
-> StateT AppStores (ExceptT ErrMsg IO) ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ErrMsg -> StateT AppStores (ExceptT ErrMsg IO) ()
dapHdl
Maybe StateTransit -> AppContext (Maybe StateTransit)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe StateTransit
forall a. Maybe a
Nothing
where
dapHdl :: String -> AppContext ()
dapHdl :: ErrMsg -> StateT AppStores (ExceptT ErrMsg IO) ()
dapHdl ErrMsg
str = case ErrMsg -> Either ErrMsg (Either ErrMsg StoppedEventBody)
forall a. Read a => ErrMsg -> Either ErrMsg a
R.readEither ErrMsg
str of
Left ErrMsg
err -> ErrMsg -> AppContext (Maybe StateTransit)
errHdl ErrMsg
err AppContext (Maybe StateTransit)
-> StateT AppStores (ExceptT ErrMsg IO) ()
-> StateT AppStores (ExceptT ErrMsg IO) ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> () -> StateT AppStores (ExceptT ErrMsg IO) ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
Right (Left ErrMsg
err) -> ErrMsg -> AppContext (Maybe StateTransit)
errHdl ErrMsg
err AppContext (Maybe StateTransit)
-> StateT AppStores (ExceptT ErrMsg IO) ()
-> StateT AppStores (ExceptT ErrMsg IO) ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> () -> StateT AppStores (ExceptT ErrMsg IO) ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
Right (Right StoppedEventBody
body) -> StoppedEventBody -> StateT AppStores (ExceptT ErrMsg IO) ()
U.handleStoppedEventBody StoppedEventBody
body
errHdl :: String -> AppContext (Maybe StateTransit)
errHdl :: ErrMsg -> AppContext (Maybe StateTransit)
errHdl ErrMsg
msg = do
IO () -> StateT AppStores (ExceptT ErrMsg IO) ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> StateT AppStores (ExceptT ErrMsg IO) ())
-> IO () -> StateT AppStores (ExceptT ErrMsg IO) ()
forall a b. (a -> b) -> a -> b
$ ErrMsg -> ErrMsg -> IO ()
L.errorM ErrMsg
_LOG_APP ErrMsg
msg
Int
resSeq <- AppContext Int
U.getIncreasedResponseSequence
let res :: ContinueResponse
res = ContinueResponse
DAP.defaultContinueResponse {
seqContinueResponse :: Int
DAP.seqContinueResponse = Int
resSeq
, request_seqContinueResponse :: Int
DAP.request_seqContinueResponse = ContinueRequest -> Int
DAP.seqContinueRequest ContinueRequest
req
, successContinueResponse :: Bool
DAP.successContinueResponse = Bool
False
, messageContinueResponse :: ErrMsg
DAP.messageContinueResponse = ErrMsg
msg
}
Response -> StateT AppStores (ExceptT ErrMsg IO) ()
U.addResponse (Response -> StateT AppStores (ExceptT ErrMsg IO) ())
-> Response -> StateT AppStores (ExceptT ErrMsg IO) ()
forall a b. (a -> b) -> a -> b
$ ContinueResponse -> Response
ContinueResponse ContinueResponse
res
Maybe StateTransit -> AppContext (Maybe StateTransit)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe StateTransit
forall a. Maybe a
Nothing