{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE StandaloneDeriving #-}

module Haskell.Debug.Adapter.Type where

import Data.Data
import Data.Default
import Control.Lens
import Data.Aeson
import Data.Aeson.TH
import Control.Monad.Except
import Control.Monad.State
import Control.Concurrent
import Control.Concurrent.Async
import qualified System.IO as S
import qualified Data.Text as T
import qualified System.Log.Logger as L
import qualified System.Process as S
import qualified Data.Version as V

import qualified Haskell.DAP as DAP
import Haskell.Debug.Adapter.TH.Utility
import Haskell.Debug.Adapter.Constant


--------------------------------------------------------------------------------
-- | Command Line Argument Data Type.
--
data ArgData = ArgData {
    ArgData -> Maybe String
_hackageVersionArgData :: Maybe String   -- ^deprecated.
  , ArgData -> Maybe String
_stdioLogFileArgData   :: Maybe FilePath -- stdio log file.
  } deriving (Typeable ArgData
ArgData -> DataType
ArgData -> Constr
(forall b. Data b => b -> b) -> ArgData -> ArgData
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> ArgData -> u
forall u. (forall d. Data d => d -> u) -> ArgData -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ArgData -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ArgData -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ArgData -> m ArgData
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ArgData -> m ArgData
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ArgData
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ArgData -> c ArgData
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ArgData)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ArgData)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ArgData -> m ArgData
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ArgData -> m ArgData
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ArgData -> m ArgData
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ArgData -> m ArgData
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ArgData -> m ArgData
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ArgData -> m ArgData
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> ArgData -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> ArgData -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> ArgData -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> ArgData -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ArgData -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ArgData -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ArgData -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ArgData -> r
gmapT :: (forall b. Data b => b -> b) -> ArgData -> ArgData
$cgmapT :: (forall b. Data b => b -> b) -> ArgData -> ArgData
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ArgData)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ArgData)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ArgData)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ArgData)
dataTypeOf :: ArgData -> DataType
$cdataTypeOf :: ArgData -> DataType
toConstr :: ArgData -> Constr
$ctoConstr :: ArgData -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ArgData
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ArgData
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ArgData -> c ArgData
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ArgData -> c ArgData
Data, Typeable, Int -> ArgData -> ShowS
[ArgData] -> ShowS
ArgData -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ArgData] -> ShowS
$cshowList :: [ArgData] -> ShowS
show :: ArgData -> String
$cshow :: ArgData -> String
showsPrec :: Int -> ArgData -> ShowS
$cshowsPrec :: Int -> ArgData -> ShowS
Show, ReadPrec [ArgData]
ReadPrec ArgData
Int -> ReadS ArgData
ReadS [ArgData]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ArgData]
$creadListPrec :: ReadPrec [ArgData]
readPrec :: ReadPrec ArgData
$creadPrec :: ReadPrec ArgData
readList :: ReadS [ArgData]
$creadList :: ReadS [ArgData]
readsPrec :: Int -> ReadS ArgData
$creadsPrec :: Int -> ReadS ArgData
Read, ArgData -> ArgData -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ArgData -> ArgData -> Bool
$c/= :: ArgData -> ArgData -> Bool
== :: ArgData -> ArgData -> Bool
$c== :: ArgData -> ArgData -> Bool
Eq)

makeLenses ''ArgData
$(deriveJSON
  defaultOptions {
      fieldLabelModifier = fieldModifier "ArgData"
    }
  ''ArgData)


-- |
--   default value instance.
--
instance Default ArgData where
  def :: ArgData
def = ArgData {
        _hackageVersionArgData :: Maybe String
_hackageVersionArgData = forall a. Maybe a
Nothing
      , _stdioLogFileArgData :: Maybe String
_stdioLogFileArgData   = forall a. Maybe a
Nothing
      }


--------------------------------------------------------------------------------
-- |
--
instance FromJSON  L.Priority  where
  parseJSON :: Value -> Parser Priority
parseJSON (String Text
v) = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall a. Read a => String -> a
read forall a b. (a -> b) -> a -> b
$ Text -> String
T.unpack Text
v
  parseJSON Value
o = forall a. HasCallStack => String -> a
error forall a b. (a -> b) -> a -> b
$ String
"json parse error. Priority:" forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show Value
o

instance ToJSON L.Priority  where
  toJSON :: Priority -> Value
toJSON (Priority
L.DEBUG)     = Text -> Value
String forall a b. (a -> b) -> a -> b
$ String -> Text
T.pack String
"DEBUG"
  toJSON (Priority
L.INFO)      = Text -> Value
String forall a b. (a -> b) -> a -> b
$ String -> Text
T.pack String
"INFO"
  toJSON (Priority
L.NOTICE)    = Text -> Value
String forall a b. (a -> b) -> a -> b
$ String -> Text
T.pack String
"NOTICE"
  toJSON (Priority
L.WARNING)   = Text -> Value
String forall a b. (a -> b) -> a -> b
$ String -> Text
T.pack String
"WARNING"
  toJSON (Priority
L.ERROR)     = Text -> Value
String forall a b. (a -> b) -> a -> b
$ String -> Text
T.pack String
"ERROR"
  toJSON (Priority
L.CRITICAL)  = Text -> Value
String forall a b. (a -> b) -> a -> b
$ String -> Text
T.pack String
"CRITICAL"
  toJSON (Priority
L.ALERT)     = Text -> Value
String forall a b. (a -> b) -> a -> b
$ String -> Text
T.pack String
"ALERT"
  toJSON (Priority
L.EMERGENCY) = Text -> Value
String forall a b. (a -> b) -> a -> b
$ String -> Text
T.pack String
"EMERGENCY"

--------------------------------------------------------------------------------
-- | Config Data
--
data ConfigData = ConfigData {
    ConfigData -> String
_workDirConfigData  :: FilePath
  , ConfigData -> String
_logFileConfigData  :: FilePath
  , ConfigData -> Priority
_logLevelConfigData :: L.Priority
  } deriving (Int -> ConfigData -> ShowS
[ConfigData] -> ShowS
ConfigData -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ConfigData] -> ShowS
$cshowList :: [ConfigData] -> ShowS
show :: ConfigData -> String
$cshow :: ConfigData -> String
showsPrec :: Int -> ConfigData -> ShowS
$cshowsPrec :: Int -> ConfigData -> ShowS
Show, ReadPrec [ConfigData]
ReadPrec ConfigData
Int -> ReadS ConfigData
ReadS [ConfigData]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ConfigData]
$creadListPrec :: ReadPrec [ConfigData]
readPrec :: ReadPrec ConfigData
$creadPrec :: ReadPrec ConfigData
readList :: ReadS [ConfigData]
$creadList :: ReadS [ConfigData]
readsPrec :: Int -> ReadS ConfigData
$creadsPrec :: Int -> ReadS ConfigData
Read, ConfigData -> ConfigData -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ConfigData -> ConfigData -> Bool
$c/= :: ConfigData -> ConfigData -> Bool
== :: ConfigData -> ConfigData -> Bool
$c== :: ConfigData -> ConfigData -> Bool
Eq)

makeLenses ''ConfigData

instance Default ConfigData where
  def :: ConfigData
def = ConfigData {
        _workDirConfigData :: String
_workDirConfigData  = String
"."
      , _logFileConfigData :: String
_logFileConfigData  = String
"haskell-debug-adapter.log"
      , _logLevelConfigData :: Priority
_logLevelConfigData = Priority
L.WARNING
      }

$(deriveJSON defaultOptions { fieldLabelModifier = fieldModifier "ConfigData" } ''ConfigData)



--------------------------------------------------------------------------------------

data StateTransit =
    Init_GHCiRun
  | Init_Shutdown
  | GHCiRun_DebugRun
  | GHCiRun_Contaminated
  | GHCiRun_Shutdown
  | DebugRun_Contaminated
  | DebugRun_Shutdown
  | DebugRun_GHCiRun
  | Contaminated_Shutdown
  deriving (Int -> StateTransit -> ShowS
[StateTransit] -> ShowS
StateTransit -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StateTransit] -> ShowS
$cshowList :: [StateTransit] -> ShowS
show :: StateTransit -> String
$cshow :: StateTransit -> String
showsPrec :: Int -> StateTransit -> ShowS
$cshowsPrec :: Int -> StateTransit -> ShowS
Show, ReadPrec [StateTransit]
ReadPrec StateTransit
Int -> ReadS StateTransit
ReadS [StateTransit]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [StateTransit]
$creadListPrec :: ReadPrec [StateTransit]
readPrec :: ReadPrec StateTransit
$creadPrec :: ReadPrec StateTransit
readList :: ReadS [StateTransit]
$creadList :: ReadS [StateTransit]
readsPrec :: Int -> ReadS StateTransit
$creadsPrec :: Int -> ReadS StateTransit
Read, StateTransit -> StateTransit -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StateTransit -> StateTransit -> Bool
$c/= :: StateTransit -> StateTransit -> Bool
== :: StateTransit -> StateTransit -> Bool
$c== :: StateTransit -> StateTransit -> Bool
Eq)

$(deriveJSON defaultOptions ''StateTransit)

--------------------------------------------------------------------------------------

data HdaInternalTransitRequest = HdaInternalTransitRequest {
    HdaInternalTransitRequest -> StateTransit
stateHdaInternalTransitRequest :: StateTransit
  } deriving (Int -> HdaInternalTransitRequest -> ShowS
[HdaInternalTransitRequest] -> ShowS
HdaInternalTransitRequest -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [HdaInternalTransitRequest] -> ShowS
$cshowList :: [HdaInternalTransitRequest] -> ShowS
show :: HdaInternalTransitRequest -> String
$cshow :: HdaInternalTransitRequest -> String
showsPrec :: Int -> HdaInternalTransitRequest -> ShowS
$cshowsPrec :: Int -> HdaInternalTransitRequest -> ShowS
Show, ReadPrec [HdaInternalTransitRequest]
ReadPrec HdaInternalTransitRequest
Int -> ReadS HdaInternalTransitRequest
ReadS [HdaInternalTransitRequest]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [HdaInternalTransitRequest]
$creadListPrec :: ReadPrec [HdaInternalTransitRequest]
readPrec :: ReadPrec HdaInternalTransitRequest
$creadPrec :: ReadPrec HdaInternalTransitRequest
readList :: ReadS [HdaInternalTransitRequest]
$creadList :: ReadS [HdaInternalTransitRequest]
readsPrec :: Int -> ReadS HdaInternalTransitRequest
$creadsPrec :: Int -> ReadS HdaInternalTransitRequest
Read, HdaInternalTransitRequest -> HdaInternalTransitRequest -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: HdaInternalTransitRequest -> HdaInternalTransitRequest -> Bool
$c/= :: HdaInternalTransitRequest -> HdaInternalTransitRequest -> Bool
== :: HdaInternalTransitRequest -> HdaInternalTransitRequest -> Bool
$c== :: HdaInternalTransitRequest -> HdaInternalTransitRequest -> Bool
Eq)

$(deriveJSON defaultOptions { fieldLabelModifier = fieldModifier "HdaInternalTransitRequest" } ''HdaInternalTransitRequest)

data HdaInternalTerminateRequest = HdaInternalTerminateRequest {
    HdaInternalTerminateRequest -> String
msgHdaInternalTerminateRequest :: String
  } deriving (Int -> HdaInternalTerminateRequest -> ShowS
[HdaInternalTerminateRequest] -> ShowS
HdaInternalTerminateRequest -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [HdaInternalTerminateRequest] -> ShowS
$cshowList :: [HdaInternalTerminateRequest] -> ShowS
show :: HdaInternalTerminateRequest -> String
$cshow :: HdaInternalTerminateRequest -> String
showsPrec :: Int -> HdaInternalTerminateRequest -> ShowS
$cshowsPrec :: Int -> HdaInternalTerminateRequest -> ShowS
Show, ReadPrec [HdaInternalTerminateRequest]
ReadPrec HdaInternalTerminateRequest
Int -> ReadS HdaInternalTerminateRequest
ReadS [HdaInternalTerminateRequest]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [HdaInternalTerminateRequest]
$creadListPrec :: ReadPrec [HdaInternalTerminateRequest]
readPrec :: ReadPrec HdaInternalTerminateRequest
$creadPrec :: ReadPrec HdaInternalTerminateRequest
readList :: ReadS [HdaInternalTerminateRequest]
$creadList :: ReadS [HdaInternalTerminateRequest]
readsPrec :: Int -> ReadS HdaInternalTerminateRequest
$creadsPrec :: Int -> ReadS HdaInternalTerminateRequest
Read, HdaInternalTerminateRequest -> HdaInternalTerminateRequest -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: HdaInternalTerminateRequest -> HdaInternalTerminateRequest -> Bool
$c/= :: HdaInternalTerminateRequest -> HdaInternalTerminateRequest -> Bool
== :: HdaInternalTerminateRequest -> HdaInternalTerminateRequest -> Bool
$c== :: HdaInternalTerminateRequest -> HdaInternalTerminateRequest -> Bool
Eq)

$(deriveJSON defaultOptions { fieldLabelModifier = fieldModifier "HdaInternalTerminateRequest" } ''HdaInternalTerminateRequest)

data HdaInternalLoadRequest = HdaInternalLoadRequest {
    HdaInternalLoadRequest -> String
pathHdaInternalLoadRequest :: FilePath
  } deriving (Int -> HdaInternalLoadRequest -> ShowS
[HdaInternalLoadRequest] -> ShowS
HdaInternalLoadRequest -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [HdaInternalLoadRequest] -> ShowS
$cshowList :: [HdaInternalLoadRequest] -> ShowS
show :: HdaInternalLoadRequest -> String
$cshow :: HdaInternalLoadRequest -> String
showsPrec :: Int -> HdaInternalLoadRequest -> ShowS
$cshowsPrec :: Int -> HdaInternalLoadRequest -> ShowS
Show, ReadPrec [HdaInternalLoadRequest]
ReadPrec HdaInternalLoadRequest
Int -> ReadS HdaInternalLoadRequest
ReadS [HdaInternalLoadRequest]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [HdaInternalLoadRequest]
$creadListPrec :: ReadPrec [HdaInternalLoadRequest]
readPrec :: ReadPrec HdaInternalLoadRequest
$creadPrec :: ReadPrec HdaInternalLoadRequest
readList :: ReadS [HdaInternalLoadRequest]
$creadList :: ReadS [HdaInternalLoadRequest]
readsPrec :: Int -> ReadS HdaInternalLoadRequest
$creadsPrec :: Int -> ReadS HdaInternalLoadRequest
Read, HdaInternalLoadRequest -> HdaInternalLoadRequest -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: HdaInternalLoadRequest -> HdaInternalLoadRequest -> Bool
$c/= :: HdaInternalLoadRequest -> HdaInternalLoadRequest -> Bool
== :: HdaInternalLoadRequest -> HdaInternalLoadRequest -> Bool
$c== :: HdaInternalLoadRequest -> HdaInternalLoadRequest -> Bool
Eq)

$(deriveJSON defaultOptions { fieldLabelModifier = fieldModifier "HdaInternalLoadRequest" } ''HdaInternalLoadRequest)

--------------------------------------------------------------------------------
-- | DAP Request Data
--


$(deriveJSON defaultOptions {fieldLabelModifier = rdrop "Source", omitNothingFields = True} ''DAP.Source)
$(deriveJSON defaultOptions {fieldLabelModifier = rdrop "SourceBreakpoint", omitNothingFields = True} ''DAP.SourceBreakpoint)
$(deriveJSON defaultOptions {fieldLabelModifier = rdrop "Breakpoint", omitNothingFields = True} ''DAP.Breakpoint)
$(deriveJSON defaultOptions {fieldLabelModifier = rdrop "FunctionBreakpoint", omitNothingFields = True} ''DAP.FunctionBreakpoint)
$(deriveJSON defaultOptions {fieldLabelModifier = rdrop "Thread", omitNothingFields = True} ''DAP.Thread)
$(deriveJSON defaultOptions {fieldLabelModifier = rdrop "StackFrame", omitNothingFields = True} ''DAP.StackFrame)
$(deriveJSON defaultOptions {fieldLabelModifier = rdrop "Scope", omitNothingFields = True} ''DAP.Scope)
$(deriveJSON defaultOptions {fieldLabelModifier = rdrop "VariablePresentationHint", omitNothingFields = True} ''DAP.VariablePresentationHint)
$(deriveJSON defaultOptions {fieldLabelModifier = rdrop "Variable", omitNothingFields = True} ''DAP.Variable)
$(deriveJSON defaultOptions {fieldLabelModifier = rdrop "CompletionsItem", omitNothingFields = True} ''DAP.CompletionsItem)


-- jsonize
$(deriveJSON defaultOptions {fieldLabelModifier = rdrop "Request", omitNothingFields = True} ''DAP.Request)

$(deriveJSON defaultOptions {fieldLabelModifier = rdrop "InitializeRequestArguments", omitNothingFields = True} ''DAP.InitializeRequestArguments)
$(deriveJSON defaultOptions {fieldLabelModifier = rdrop "InitializeRequest", omitNothingFields = True} ''DAP.InitializeRequest)

$(deriveJSON defaultOptions {fieldLabelModifier = rdrop "LaunchRequestArguments", omitNothingFields = True} ''DAP.LaunchRequestArguments)
$(deriveJSON defaultOptions {fieldLabelModifier = rdrop "LaunchRequest", omitNothingFields = True} ''DAP.LaunchRequest)

$(deriveJSON defaultOptions {fieldLabelModifier = rdrop "DisconnectRequestArguments", omitNothingFields = True} ''DAP.DisconnectRequestArguments)
$(deriveJSON defaultOptions {fieldLabelModifier = rdrop "DisconnectRequest", omitNothingFields = True} ''DAP.DisconnectRequest)

$(deriveJSON defaultOptions {fieldLabelModifier = rdrop "PauseRequestArguments", omitNothingFields = True} ''DAP.PauseRequestArguments)
$(deriveJSON defaultOptions {fieldLabelModifier = rdrop "PauseRequest", omitNothingFields = True} ''DAP.PauseRequest)

$(deriveJSON defaultOptions {fieldLabelModifier = rdrop "TerminateRequestArguments", omitNothingFields = True} ''DAP.TerminateRequestArguments)
$(deriveJSON defaultOptions {fieldLabelModifier = rdrop "TerminateRequest", omitNothingFields = True} ''DAP.TerminateRequest)

$(deriveJSON defaultOptions {fieldLabelModifier = rdrop "SetBreakpointsRequestArguments", omitNothingFields = True} ''DAP.SetBreakpointsRequestArguments)
$(deriveJSON defaultOptions {fieldLabelModifier = rdrop "SetBreakpointsRequest", omitNothingFields = True} ''DAP.SetBreakpointsRequest)

$(deriveJSON defaultOptions {fieldLabelModifier = rdrop "SetFunctionBreakpointsRequestArguments", omitNothingFields = True} ''DAP.SetFunctionBreakpointsRequestArguments)
$(deriveJSON defaultOptions {fieldLabelModifier = rdrop "SetFunctionBreakpointsRequest", omitNothingFields = True} ''DAP.SetFunctionBreakpointsRequest)

$(deriveJSON defaultOptions {fieldLabelModifier = rdrop "SetExceptionBreakpointsRequestArguments", omitNothingFields = True} ''DAP.SetExceptionBreakpointsRequestArguments)
$(deriveJSON defaultOptions {fieldLabelModifier = rdrop "SetExceptionBreakpointsRequest", omitNothingFields = True} ''DAP.SetExceptionBreakpointsRequest)

$(deriveJSON defaultOptions {fieldLabelModifier = rdrop "ConfigurationDoneRequest", omitNothingFields = True} ''DAP.ConfigurationDoneRequest)

$(deriveJSON defaultOptions {fieldLabelModifier = rdrop "ThreadsRequest", omitNothingFields = True} ''DAP.ThreadsRequest)

$(deriveJSON defaultOptions {fieldLabelModifier = rdrop "StackTraceRequestArguments", omitNothingFields = True} ''DAP.StackTraceRequestArguments)
$(deriveJSON defaultOptions {fieldLabelModifier = rdrop "StackTraceRequest", omitNothingFields = True} ''DAP.StackTraceRequest)

$(deriveJSON defaultOptions {fieldLabelModifier = rdrop "ScopesRequestArguments", omitNothingFields = True} ''DAP.ScopesRequestArguments)
$(deriveJSON defaultOptions {fieldLabelModifier = rdrop "ScopesRequest", omitNothingFields = True} ''DAP.ScopesRequest)

$(deriveJSON defaultOptions {fieldLabelModifier = rdrop "VariablesRequestArguments", omitNothingFields = True} ''DAP.VariablesRequestArguments)
$(deriveJSON defaultOptions {fieldLabelModifier = rdrop "VariablesRequest", omitNothingFields = True} ''DAP.VariablesRequest)

$(deriveJSON defaultOptions {fieldLabelModifier = rdrop "SourceRequestArguments", omitNothingFields = True} ''DAP.SourceRequestArguments)
$(deriveJSON defaultOptions {fieldLabelModifier = rdrop "SourceRequest", omitNothingFields = True} ''DAP.SourceRequest)

$(deriveJSON defaultOptions {fieldLabelModifier = rdrop "ContinueRequestArguments", omitNothingFields = True} ''DAP.ContinueRequestArguments)
$(deriveJSON defaultOptions {fieldLabelModifier = rdrop "ContinueRequest", omitNothingFields = True} ''DAP.ContinueRequest)

$(deriveJSON defaultOptions {fieldLabelModifier = rdrop "NextRequestArguments", omitNothingFields = True} ''DAP.NextRequestArguments)
$(deriveJSON defaultOptions {fieldLabelModifier = rdrop "NextRequest", omitNothingFields = True} ''DAP.NextRequest)

$(deriveJSON defaultOptions {fieldLabelModifier = rdrop "StepInRequestArguments", omitNothingFields = True} ''DAP.StepInRequestArguments)
$(deriveJSON defaultOptions {fieldLabelModifier = rdrop "StepInRequest", omitNothingFields = True} ''DAP.StepInRequest)

$(deriveJSON defaultOptions {fieldLabelModifier = rdrop "EvaluateRequestArguments", omitNothingFields = True} ''DAP.EvaluateRequestArguments)
$(deriveJSON defaultOptions {fieldLabelModifier = rdrop "EvaluateRequest", omitNothingFields = True} ''DAP.EvaluateRequest)

$(deriveJSON defaultOptions {fieldLabelModifier = rdrop "CompletionsRequestArguments", omitNothingFields = True} ''DAP.CompletionsRequestArguments)
$(deriveJSON defaultOptions {fieldLabelModifier = rdrop "CompletionsRequest", omitNothingFields = True} ''DAP.CompletionsRequest)


-- request
data Request a where
  InitializeRequest :: DAP.InitializeRequest -> Request DAP.InitializeRequest
  LaunchRequest     :: DAP.LaunchRequest     -> Request DAP.LaunchRequest
  DisconnectRequest :: DAP.DisconnectRequest -> Request DAP.DisconnectRequest
  PauseRequest :: DAP.PauseRequest -> Request DAP.PauseRequest
  TerminateRequest :: DAP.TerminateRequest -> Request DAP.TerminateRequest
  SetBreakpointsRequest :: DAP.SetBreakpointsRequest -> Request DAP.SetBreakpointsRequest
  SetFunctionBreakpointsRequest :: DAP.SetFunctionBreakpointsRequest -> Request DAP.SetFunctionBreakpointsRequest
  SetExceptionBreakpointsRequest :: DAP.SetExceptionBreakpointsRequest -> Request DAP.SetExceptionBreakpointsRequest
  ConfigurationDoneRequest :: DAP.ConfigurationDoneRequest -> Request DAP.ConfigurationDoneRequest
  ThreadsRequest :: DAP.ThreadsRequest -> Request DAP.ThreadsRequest
  StackTraceRequest :: DAP.StackTraceRequest -> Request DAP.StackTraceRequest
  ScopesRequest :: DAP.ScopesRequest -> Request DAP.ScopesRequest
  VariablesRequest :: DAP.VariablesRequest -> Request DAP.VariablesRequest
  SourceRequest :: DAP.SourceRequest -> Request DAP.SourceRequest
  ContinueRequest :: DAP.ContinueRequest -> Request DAP.ContinueRequest
  NextRequest :: DAP.NextRequest -> Request DAP.NextRequest
  StepInRequest :: DAP.StepInRequest -> Request DAP.StepInRequest
  EvaluateRequest :: DAP.EvaluateRequest -> Request DAP.EvaluateRequest
  CompletionsRequest :: DAP.CompletionsRequest -> Request DAP.CompletionsRequest
  InternalTransitRequest :: HdaInternalTransitRequest -> Request HdaInternalTransitRequest
  InternalTerminateRequest :: HdaInternalTerminateRequest -> Request HdaInternalTerminateRequest
  InternalLoadRequest :: HdaInternalLoadRequest -> Request HdaInternalLoadRequest

deriving instance Show r => Show (Request r)

data WrapRequest = forall a. WrapRequest (Request a)

--------------------------------------------------------------------------------
-- | DAP Response Data
--

-- jsonize
$(deriveJSON defaultOptions {fieldLabelModifier = rdrop "Response", omitNothingFields = True} ''DAP.Response)
$(deriveJSON defaultOptions {fieldLabelModifier = rdrop "ColumnDescriptor", omitNothingFields = True} ''DAP.ColumnDescriptor)
$(deriveJSON defaultOptions {fieldLabelModifier = rdrop "ExceptionBreakpointsFilter", omitNothingFields = True} ''DAP.ExceptionBreakpointsFilter)

$(deriveJSON defaultOptions {fieldLabelModifier = rdrop "InitializeResponseBody", omitNothingFields = True} ''DAP.InitializeResponseBody)
$(deriveJSON defaultOptions {fieldLabelModifier = rdrop "InitializeResponse", omitNothingFields = True} ''DAP.InitializeResponse)

$(deriveJSON defaultOptions {fieldLabelModifier = rdrop "LaunchResponse", omitNothingFields = True} ''DAP.LaunchResponse)

$(deriveJSON defaultOptions {fieldLabelModifier = rdrop "OutputEventBody", omitNothingFields = True} ''DAP.OutputEventBody)
$(deriveJSON defaultOptions {fieldLabelModifier = rdrop "OutputEvent", omitNothingFields = True} ''DAP.OutputEvent)

$(deriveJSON defaultOptions {fieldLabelModifier = rdrop "StoppedEventBody", omitNothingFields = True} ''DAP.StoppedEventBody)
$(deriveJSON defaultOptions {fieldLabelModifier = rdrop "StoppedEvent", omitNothingFields = True} ''DAP.StoppedEvent)

$(deriveJSON defaultOptions {fieldLabelModifier = rdrop "InitializedEvent", omitNothingFields = True} ''DAP.InitializedEvent)

$(deriveJSON defaultOptions {fieldLabelModifier = rdrop "DisconnectResponse", omitNothingFields = True} ''DAP.DisconnectResponse)

$(deriveJSON defaultOptions {fieldLabelModifier = rdrop "PauseResponse", omitNothingFields = True} ''DAP.PauseResponse)

$(deriveJSON defaultOptions {fieldLabelModifier = rdrop "TerminateResponse", omitNothingFields = True} ''DAP.TerminateResponse)

$(deriveJSON defaultOptions {fieldLabelModifier = rdrop "SetBreakpointsResponseBody", omitNothingFields = True} ''DAP.SetBreakpointsResponseBody)
$(deriveJSON defaultOptions {fieldLabelModifier = rdrop "SetBreakpointsResponse", omitNothingFields = True} ''DAP.SetBreakpointsResponse)

$(deriveJSON defaultOptions {fieldLabelModifier = rdrop "SetFunctionBreakpointsResponseBody", omitNothingFields = True} ''DAP.SetFunctionBreakpointsResponseBody)
$(deriveJSON defaultOptions {fieldLabelModifier = rdrop "SetFunctionBreakpointsResponse", omitNothingFields = True} ''DAP.SetFunctionBreakpointsResponse)

$(deriveJSON defaultOptions {fieldLabelModifier = rdrop "SetExceptionBreakpointsResponse", omitNothingFields = True} ''DAP.SetExceptionBreakpointsResponse)

$(deriveJSON defaultOptions {fieldLabelModifier = rdrop "ConfigurationDoneResponse", omitNothingFields = True} ''DAP.ConfigurationDoneResponse)

$(deriveJSON defaultOptions {fieldLabelModifier = rdrop "ThreadsResponseBody", omitNothingFields = True} ''DAP.ThreadsResponseBody)
$(deriveJSON defaultOptions {fieldLabelModifier = rdrop "ThreadsResponse", omitNothingFields = True} ''DAP.ThreadsResponse)

$(deriveJSON defaultOptions {fieldLabelModifier = rdrop "StackTraceResponseBody", omitNothingFields = True} ''DAP.StackTraceResponseBody)
$(deriveJSON defaultOptions {fieldLabelModifier = rdrop "StackTraceResponse", omitNothingFields = True} ''DAP.StackTraceResponse)

$(deriveJSON defaultOptions {fieldLabelModifier = rdrop "ScopesResponseBody", omitNothingFields = True} ''DAP.ScopesResponseBody)
$(deriveJSON defaultOptions {fieldLabelModifier = rdrop "ScopesResponse", omitNothingFields = True} ''DAP.ScopesResponse)

$(deriveJSON defaultOptions {fieldLabelModifier = rdrop "VariablesResponseBody", omitNothingFields = True} ''DAP.VariablesResponseBody)
$(deriveJSON defaultOptions {fieldLabelModifier = rdrop "VariablesResponse", omitNothingFields = True} ''DAP.VariablesResponse)

$(deriveJSON defaultOptions {fieldLabelModifier = rdrop "SourceResponseBody", omitNothingFields = True} ''DAP.SourceResponseBody)
$(deriveJSON defaultOptions {fieldLabelModifier = rdrop "SourceResponse", omitNothingFields = True} ''DAP.SourceResponse)

$(deriveJSON defaultOptions {fieldLabelModifier = rdrop "ContinueResponse", omitNothingFields = True} ''DAP.ContinueResponse)

$(deriveJSON defaultOptions {fieldLabelModifier = rdrop "NextResponse", omitNothingFields = True} ''DAP.NextResponse)

$(deriveJSON defaultOptions {fieldLabelModifier = rdrop "StepInResponse", omitNothingFields = True} ''DAP.StepInResponse)

$(deriveJSON defaultOptions {fieldLabelModifier = rdrop "EvaluateResponseBody", omitNothingFields = True} ''DAP.EvaluateResponseBody)
$(deriveJSON defaultOptions {fieldLabelModifier = rdrop "EvaluateResponse", omitNothingFields = True} ''DAP.EvaluateResponse)

$(deriveJSON defaultOptions {fieldLabelModifier = rdrop "CompletionsResponseBody", omitNothingFields = True} ''DAP.CompletionsResponseBody)
$(deriveJSON defaultOptions {fieldLabelModifier = rdrop "CompletionsResponse", omitNothingFields = True} ''DAP.CompletionsResponse)

$(deriveJSON defaultOptions {fieldLabelModifier = rdrop "TerminatedEventBody", omitNothingFields = True} ''DAP.TerminatedEventBody)
$(deriveJSON defaultOptions {fieldLabelModifier = rdrop "TerminatedEvent", omitNothingFields = True} ''DAP.TerminatedEvent)

$(deriveJSON defaultOptions {fieldLabelModifier = rdrop "ExitedEventBody", omitNothingFields = True} ''DAP.ExitedEventBody)
$(deriveJSON defaultOptions {fieldLabelModifier = rdrop "ExitedEvent", omitNothingFields = True} ''DAP.ExitedEvent)

$(deriveJSON defaultOptions {fieldLabelModifier = rdrop "ContinuedEventBody", omitNothingFields = True} ''DAP.ContinuedEventBody)
$(deriveJSON defaultOptions {fieldLabelModifier = rdrop "ContinuedEvent", omitNothingFields = True} ''DAP.ContinuedEvent)


-- response
data Response =
    InitializeResponse DAP.InitializeResponse
  | LaunchResponse     DAP.LaunchResponse
  | OutputEvent        DAP.OutputEvent
  | StoppedEvent       DAP.StoppedEvent
  | TerminatedEvent    DAP.TerminatedEvent
  | ExitedEvent        DAP.ExitedEvent
  | ContinuedEvent     DAP.ContinuedEvent
  | InitializedEvent   DAP.InitializedEvent
  | DisconnectResponse DAP.DisconnectResponse
  | PauseResponse DAP.PauseResponse
  | TerminateResponse DAP.TerminateResponse
  | SetBreakpointsResponse DAP.SetBreakpointsResponse
  | SetFunctionBreakpointsResponse DAP.SetFunctionBreakpointsResponse
  | SetExceptionBreakpointsResponse DAP.SetExceptionBreakpointsResponse
  | ConfigurationDoneResponse DAP.ConfigurationDoneResponse
  | ThreadsResponse DAP.ThreadsResponse
  | StackTraceResponse DAP.StackTraceResponse
  | ScopesResponse DAP.ScopesResponse
  | VariablesResponse DAP.VariablesResponse
  | SourceResponse DAP.SourceResponse
  | ContinueResponse DAP.ContinueResponse
  | NextResponse DAP.NextResponse
  | StepInResponse DAP.StepInResponse
  | EvaluateResponse DAP.EvaluateResponse
  | CompletionsResponse DAP.CompletionsResponse
  deriving (Int -> Response -> ShowS
[Response] -> ShowS
Response -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Response] -> ShowS
$cshowList :: [Response] -> ShowS
show :: Response -> String
$cshow :: Response -> String
showsPrec :: Int -> Response -> ShowS
$cshowsPrec :: Int -> Response -> ShowS
Show, ReadPrec [Response]
ReadPrec Response
Int -> ReadS Response
ReadS [Response]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Response]
$creadListPrec :: ReadPrec [Response]
readPrec :: ReadPrec Response
$creadPrec :: ReadPrec Response
readList :: ReadS [Response]
$creadList :: ReadS [Response]
readsPrec :: Int -> ReadS Response
$creadsPrec :: Int -> ReadS Response
Read, Response -> Response -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Response -> Response -> Bool
$c/= :: Response -> Response -> Bool
== :: Response -> Response -> Bool
$c== :: Response -> Response -> Bool
Eq)

$(deriveJSON defaultOptions{sumEncoding = UntaggedValue} ''Response)

--------------------------------------------------------------------------------
-- | State
--
data InitStateData         = InitStateData deriving (Int -> InitStateData -> ShowS
[InitStateData] -> ShowS
InitStateData -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [InitStateData] -> ShowS
$cshowList :: [InitStateData] -> ShowS
show :: InitStateData -> String
$cshow :: InitStateData -> String
showsPrec :: Int -> InitStateData -> ShowS
$cshowsPrec :: Int -> InitStateData -> ShowS
Show, InitStateData -> InitStateData -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: InitStateData -> InitStateData -> Bool
$c/= :: InitStateData -> InitStateData -> Bool
== :: InitStateData -> InitStateData -> Bool
$c== :: InitStateData -> InitStateData -> Bool
Eq)
data GHCiRunStateData      = GHCiRunStateData deriving (Int -> GHCiRunStateData -> ShowS
[GHCiRunStateData] -> ShowS
GHCiRunStateData -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GHCiRunStateData] -> ShowS
$cshowList :: [GHCiRunStateData] -> ShowS
show :: GHCiRunStateData -> String
$cshow :: GHCiRunStateData -> String
showsPrec :: Int -> GHCiRunStateData -> ShowS
$cshowsPrec :: Int -> GHCiRunStateData -> ShowS
Show, GHCiRunStateData -> GHCiRunStateData -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GHCiRunStateData -> GHCiRunStateData -> Bool
$c/= :: GHCiRunStateData -> GHCiRunStateData -> Bool
== :: GHCiRunStateData -> GHCiRunStateData -> Bool
$c== :: GHCiRunStateData -> GHCiRunStateData -> Bool
Eq)
data DebugRunStateData     = DebugRunStateData deriving (Int -> DebugRunStateData -> ShowS
[DebugRunStateData] -> ShowS
DebugRunStateData -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DebugRunStateData] -> ShowS
$cshowList :: [DebugRunStateData] -> ShowS
show :: DebugRunStateData -> String
$cshow :: DebugRunStateData -> String
showsPrec :: Int -> DebugRunStateData -> ShowS
$cshowsPrec :: Int -> DebugRunStateData -> ShowS
Show, DebugRunStateData -> DebugRunStateData -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DebugRunStateData -> DebugRunStateData -> Bool
$c/= :: DebugRunStateData -> DebugRunStateData -> Bool
== :: DebugRunStateData -> DebugRunStateData -> Bool
$c== :: DebugRunStateData -> DebugRunStateData -> Bool
Eq)
data ContaminatedStateData = ContaminatedStateData deriving (Int -> ContaminatedStateData -> ShowS
[ContaminatedStateData] -> ShowS
ContaminatedStateData -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ContaminatedStateData] -> ShowS
$cshowList :: [ContaminatedStateData] -> ShowS
show :: ContaminatedStateData -> String
$cshow :: ContaminatedStateData -> String
showsPrec :: Int -> ContaminatedStateData -> ShowS
$cshowsPrec :: Int -> ContaminatedStateData -> ShowS
Show, ContaminatedStateData -> ContaminatedStateData -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ContaminatedStateData -> ContaminatedStateData -> Bool
$c/= :: ContaminatedStateData -> ContaminatedStateData -> Bool
== :: ContaminatedStateData -> ContaminatedStateData -> Bool
$c== :: ContaminatedStateData -> ContaminatedStateData -> Bool
Eq)
data ShutdownStateData     = ShutdownStateData deriving (Int -> ShutdownStateData -> ShowS
[ShutdownStateData] -> ShowS
ShutdownStateData -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ShutdownStateData] -> ShowS
$cshowList :: [ShutdownStateData] -> ShowS
show :: ShutdownStateData -> String
$cshow :: ShutdownStateData -> String
showsPrec :: Int -> ShutdownStateData -> ShowS
$cshowsPrec :: Int -> ShutdownStateData -> ShowS
Show, ShutdownStateData -> ShutdownStateData -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ShutdownStateData -> ShutdownStateData -> Bool
$c/= :: ShutdownStateData -> ShutdownStateData -> Bool
== :: ShutdownStateData -> ShutdownStateData -> Bool
$c== :: ShutdownStateData -> ShutdownStateData -> Bool
Eq)

data AppState s where
  InitState     :: AppState InitStateData
  GHCiRunState  :: AppState GHCiRunStateData
  DebugRunState :: AppState DebugRunStateData
  ShutdownState :: AppState ShutdownStateData
  ContaminatedState :: AppState ContaminatedStateData

deriving instance Show s => Show (AppState s)

class AppStateIF s where
  entryAction :: (AppState s) -> AppContext ()
  exitAction  :: (AppState s) -> AppContext ()
  doActivity  :: (AppState s) -> WrapRequest -> AppContext (Maybe StateTransit)

data WrapAppState = forall s. (AppStateIF s) => WrapAppState (AppState s)

class WrapAppStateIF s where
  entryActionW :: s -> AppContext ()
  exitActionW  :: s -> AppContext ()
  doActivityW  :: s -> WrapRequest -> AppContext (Maybe StateTransit)

instance WrapAppStateIF WrapAppState where
  entryActionW :: WrapAppState -> AppContext ()
entryActionW (WrapAppState AppState s
s) = forall s. AppStateIF s => AppState s -> AppContext ()
entryAction AppState s
s
  exitActionW :: WrapAppState -> AppContext ()
exitActionW  (WrapAppState AppState s
s) = forall s. AppStateIF s => AppState s -> AppContext ()
exitAction AppState s
s
  doActivityW :: WrapAppState -> WrapRequest -> AppContext (Maybe StateTransit)
doActivityW  (WrapAppState AppState s
s) WrapRequest
r = forall s.
AppStateIF s =>
AppState s -> WrapRequest -> AppContext (Maybe StateTransit)
doActivity AppState s
s WrapRequest
r

-- |
--
class  (Show s, Show r) => StateActivityIF s r where
  action :: (AppState s) -> (Request r) -> AppContext (Maybe StateTransit)
  --action _ _ = return Nothing
  action AppState s
s Request r
r = do
    forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ String -> String -> IO ()
L.warningM String
_LOG_APP forall a b. (a -> b) -> a -> b
$ forall a. Show a => a -> String
show AppState s
s forall a. [a] -> [a] -> [a]
++ String
" " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show Request r
r forall a. [a] -> [a] -> [a]
++ String
" not supported. nop."
    forall (m :: * -> *) a. Monad m => a -> m a
return forall a. Maybe a
Nothing

--------------------------------------------------------------------------------
-- | Event
--
data Event =
  CriticalExitEvent
  deriving (Int -> Event -> ShowS
[Event] -> ShowS
Event -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Event] -> ShowS
$cshowList :: [Event] -> ShowS
show :: Event -> String
$cshow :: Event -> String
showsPrec :: Int -> Event -> ShowS
$cshowsPrec :: Int -> Event -> ShowS
Show, ReadPrec [Event]
ReadPrec Event
Int -> ReadS Event
ReadS [Event]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Event]
$creadListPrec :: ReadPrec [Event]
readPrec :: ReadPrec Event
$creadPrec :: ReadPrec Event
readList :: ReadS [Event]
$creadList :: ReadS [Event]
readsPrec :: Int -> ReadS Event
$creadsPrec :: Int -> ReadS Event
Read, Event -> Event -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Event -> Event -> Bool
$c/= :: Event -> Event -> Bool
== :: Event -> Event -> Bool
$c== :: Event -> Event -> Bool
Eq)


--------------------------------------------------------------------------------
-- |
--
data GHCiProc = GHCiProc {
    GHCiProc -> Handle
_wHdLGHCiProc :: S.Handle
  , GHCiProc -> Handle
_rHdlGHCiProc :: S.Handle
  , GHCiProc -> Handle
_errGHCiProc  :: S.Handle
  , GHCiProc -> ProcessHandle
_procGHCiProc :: S.ProcessHandle
  }


--------------------------------------------------------------------------------
-- | Application Context
--

type ErrMsg = String
type AppContext = StateT AppStores (ExceptT ErrMsg IO)


-- | Application Context Data
--
data AppStores = AppStores {
  -- Read Only
    AppStores -> String
_appNameAppStores     :: String
  , AppStores -> String
_appVerAppStores      :: String
  , AppStores -> Handle
_inHandleAppStores    :: S.Handle
  , AppStores -> Handle
_outHandleAppStores   :: S.Handle
  , AppStores -> [Async ()]
_asyncsAppStores      :: [Async ()]
  , AppStores -> Maybe String
_stdioLogFileAppStores :: Maybe FilePath

  -- Read/Write from Application
  , AppStores -> WrapAppState
_appStateWAppStores   :: WrapAppState
  , AppStores -> Int
_resSeqAppStores      :: Int
  , AppStores -> String
_startupAppStores     :: FilePath
  , AppStores -> String
_startupFuncAppStores :: String
  , AppStores -> String
_startupArgsAppStores :: String
  , AppStores -> Bool
_stopOnEntryAppStores :: Bool
  , AppStores -> String
_ghciPmptAppStores    :: String
  , AppStores -> String
_mainArgsAppStores    :: String
  , AppStores -> Int
_launchReqSeqAppStores :: Int
  , AppStores -> Bool
_debugReRunableAppStores :: Bool

  -- Global Read/Write ASync
  , AppStores -> MVar [WrapRequest]
_reqStoreAppStores    :: MVar [WrapRequest]
  , AppStores -> MVar [Response]
_resStoreAppStores    :: MVar [Response]
  , AppStores -> MVar [Event]
_eventStoreAppStores  :: MVar [Event]
  , AppStores -> MVar String
_workspaceAppStores   :: MVar FilePath
  , AppStores -> MVar Priority
_logPriorityAppStores :: MVar L.Priority
  , AppStores -> MVar GHCiProc
_ghciProcAppStores    :: MVar GHCiProc
  --, _ghciStdoutAppStores  :: MVar B.ByteString
  , AppStores -> MVar Version
_ghciVerAppStores     :: MVar V.Version
  }

makeLenses ''AppStores
makeLenses ''GHCiProc