{-# LANGUAGE MultiParamTypeClasses #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}

module Haskell.Debug.Adapter.State.DebugRun.StepIn 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

-- |
--  Any errors should be sent back as False result Response
--
instance StateActivityIF DebugRunStateData DAP.StepInRequest where
  action :: AppState DebugRunStateData
-> Request StepInRequest -> AppContext (Maybe StateTransit)
action AppState DebugRunStateData
_ (StepInRequest StepInRequest
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 StepInRequest called. " ErrMsg -> ErrMsg -> ErrMsg
forall a. [a] -> [a] -> [a]
++ StepInRequest -> ErrMsg
forall a. Show a => a -> ErrMsg
show StepInRequest
req
    StepInRequest -> AppContext (Maybe StateTransit)
app StepInRequest
req

-- |
--
app :: DAP.StepInRequest -> AppContext (Maybe StateTransit)
app :: StepInRequest -> AppContext (Maybe StateTransit)
app StepInRequest
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 :: StepInRequestArguments
args = StepInRequest -> StepInRequestArguments
DAP.argumentsStepInRequest StepInRequest
req
      dap :: ErrMsg
dap = ErrMsg
":dap-step-in "
      cmd :: ErrMsg
cmd = ErrMsg
dap ErrMsg -> ErrMsg -> ErrMsg
forall a. [a] -> [a] -> [a]
++ StepInRequestArguments -> ErrMsg
forall a. Show a => a -> ErrMsg
U.showDAP StepInRequestArguments
args
      dbg :: ErrMsg
dbg = ErrMsg
dap ErrMsg -> ErrMsg -> ErrMsg
forall a. [a] -> [a] -> [a]
++ StepInRequestArguments -> ErrMsg
forall a. Show a => a -> ErrMsg
show StepInRequestArguments
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 :: StepInResponse
res = StepInResponse
DAP.defaultStepInResponse {
            seqStepInResponse :: Int
DAP.seqStepInResponse = Int
resSeq
          , request_seqStepInResponse :: Int
DAP.request_seqStepInResponse = StepInRequest -> Int
DAP.seqStepInRequest StepInRequest
req
          , successStepInResponse :: Bool
DAP.successStepInResponse = 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
$ StepInResponse -> Response
StepInResponse StepInResponse
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 :: StepInResponse
res = StepInResponse
DAP.defaultStepInResponse {
                seqStepInResponse :: Int
DAP.seqStepInResponse = Int
resSeq
              , request_seqStepInResponse :: Int
DAP.request_seqStepInResponse = StepInRequest -> Int
DAP.seqStepInRequest StepInRequest
req
              , successStepInResponse :: Bool
DAP.successStepInResponse = Bool
False
              , messageStepInResponse :: ErrMsg
DAP.messageStepInResponse = 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
$ StepInResponse -> Response
StepInResponse StepInResponse
res
      Maybe StateTransit -> AppContext (Maybe StateTransit)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe StateTransit
forall a. Maybe a
Nothing