{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE DerivingStrategies         #-}
{-# LANGUAGE OverloadedStrings          #-}
{-# LANGUAGE UndecidableInstances       #-}
{-# LANGUAGE TypeApplications           #-}
{-# LANGUAGE RecordWildCards            #-}
{-# LANGUAGE DeriveAnyClass             #-}
{-# LANGUAGE DeriveGeneric              #-}
{-# LANGUAGE LambdaCase                 #-}
module DAP.Types
  ( 
    MessageType                        (..)
    
  , Breakpoint                         (..)
  , Breakpoints                        (..)
  , BreakpointLocation                 (..)
  , Capabilities                       (..)
  , Checksum                           (..)
  , ChecksumAlgorithm                  (..)
  , ColumnDescriptor                   (..)
  , CompletionItem                     (..)
  , CompletionItemType                 (..)
  , DataBreakpoint                     (..)
  , DataBreakpointAccessType           (..)
  , DisassembledInstruction            (..)
  , ExceptionBreakMode                 (..)
  , ExceptionBreakpointsFilter         (..)
  , ExceptionDetails                   (..)
  , ExceptionFilterOptions             (..)
  , ExceptionOptions                   (..)
  , ExceptionPathSegment               (..)
  , FunctionBreakpoint                 (..)
  , GotoTarget                         (..)
  , InstructionBreakpoint              (..)
  , InvalidatedAreas                   (..)
  , Message                            (..)
  , Module                             (..)
  , ModulesViewDescriptor              (..)
  , PresentationHint                   (..)
  , Scope                              (..)
  , Source                             (..)
  , SourceBreakpoint                   (..)
  , SourcePresentationHint             (..)
  , StackFrame                         (..)
  , StackFrameFormat                   (..)
  , StepInTarget                       (..)
  , SteppingGranularity                (..)
  , StoppedEventReason                 (..)
  , Thread                             (..)
  , ThreadEventReason                  (..)
  , ValueFormat                        (..)
  , Variable                           (..)
  , VariablePresentationHint           (..)
  , ColumnDescriptorType               (..)
  , ScopePresentationHint              (..)
  , PresentationHintKind               (..)
  , PresentationHintAttributes         (..)
  , PresentationHintVisibility         (..)
  , EventGroup                         (..)
  , EventReason                        (..)
  , StartMethod                        (..)
  , EvaluateArgumentsContext           (..)
  , PathFormat                         (..)
    
  , Command                            (..)
    
  , ReverseCommand                     (..)
    
  , EventType                          (..)
    
  , StoppedEvent                       (..)
  , ContinuedEvent                     (..)
  , ExitedEvent                        (..)
  , TerminatedEvent                    (..)
  , ThreadEvent                        (..)
  , OutputEvent                        (..)
  , OutputEventCategory                (..)
  , BreakpointEvent                    (..)
  , ModuleEvent                        (..)
  , LoadedSourceEvent                  (..)
  , ProcessEvent                       (..)
  , CapabilitiesEvent                  (..)
  , ProgressStartEvent                 (..)
  , ProgressUpdateEvent                (..)
  , ProgressEndEvent                   (..)
  , InvalidatedEvent                   (..)
  , MemoryEvent                        (..)
    
  , ServerConfig                       (..)
    
  , Adaptor                            (..)
  , AdaptorState                       (..)
  , AdaptorLocal(..)
  , AppStore
  , MonadIO
    
  , AdaptorException                   (..)
  , ErrorMessage                       (..)
  , ErrorResponse                      (..)
    
  , Request                            (..)
  , ReverseRequestResponse             (..)
    
  , PayloadSize
  , Seq
  , SessionId
    
  , CompletionsResponse                (..)
  , ContinueResponse                   (..)
  , DataBreakpointInfoResponse         (..)
  , DisassembleResponse                (..)
  , EvaluateResponse                   (..)
  , ExceptionInfoResponse              (..)
  , GotoTargetsResponse                (..)
  , LoadedSourcesResponse              (..)
  , ModulesResponse                    (..)
  , ReadMemoryResponse                 (..)
  , RunInTerminalResponse              (..)
  , ScopesResponse                     (..)
  , SetExpressionResponse              (..)
  , SetVariableResponse                (..)
  , SourceResponse                     (..)
  , StackTraceResponse                 (..)
  , StepInTargetsResponse              (..)
  , ThreadsResponse                    (..)
  , VariablesResponse                  (..)
  , WriteMemoryResponse                (..)
    
  , AttachRequestArguments             (..)
  , BreakpointLocationsArguments       (..)
  , CompletionsArguments               (..)
  , ConfigurationDoneArguments         (..)
  , ContinueArguments                  (..)
  , DataBreakpointInfoArguments        (..)
  , DisassembleArguments               (..)
  , DisconnectArguments                (..)
  , EvaluateArguments                  (..)
  , ExceptionInfoArguments             (..)
  , GotoArguments                      (..)
  , GotoTargetsArguments               (..)
  , InitializeRequestArguments         (..)
  , LaunchRequestArguments             (..)
  , LoadedSourcesArguments             (..)
  , ModulesArguments                   (..)
  , NextArguments                      (..)
  , PauseArguments                     (..)
  , ReadMemoryArguments                (..)
  , RestartArguments                   (..)
  , RestartFrameArguments              (..)
  , ReverseContinueArguments           (..)
  , RunInTerminalRequestArguments      (..)
  , RunInTerminalRequestArgumentsKind  (..)
  , ScopesArguments                    (..)
  , SetBreakpointsArguments            (..)
  , SetDataBreakpointsArguments        (..)
  , SetExceptionBreakpointsArguments   (..)
  , SetExpressionArguments             (..)
  , SetFunctionBreakpointsArguments    (..)
  , SetInstructionBreakpointsArguments (..)
  , SetVariableArguments               (..)
  , SourceArguments                    (..)
  , StackTraceArguments                (..)
  , StepBackArguments                  (..)
  , StepInArguments                    (..)
  , StepInTargetsArguments             (..)
  , StepOutArguments                   (..)
  , TerminateArguments                 (..)
  , TerminateThreadsArguments          (..)
  , ThreadsArguments                   (..)
  , VariablesArguments                 (..)
  , WriteMemoryArguments               (..)
    
  , defaultBreakpoint
  , defaultBreakpointLocation
  , defaultCapabilities
  , defaultColumnDescriptor
  , defaultCompletionItem
  , defaultDisassembledInstruction
  , defaultExceptionBreakpointsFilter
  , defaultExceptionDetails
  , defaultFunctionBreakpoint
  , defaultGotoTarget
  , defaultMessage
  , defaultModule
  , defaultModulesViewDescriptor
  , defaultScope
  , defaultSource
  , defaultSourceBreakpoint
  , defaultStackFrame
  , defaultStackFrameFormat
  , defaultStepInTarget
  , defaultThread
  , defaultValueFormat
  , defaultVariable
  , defaultVariablePresentationHint
  
  , DebuggerThreadState (..)
  ) where
import           Control.Applicative             ( (<|>) )
import           Control.Monad.Base              ( MonadBase )
import           Control.Monad.Except            ( MonadError, ExceptT )
import           Control.Monad.Trans.Control     ( MonadBaseControl )
import           Control.Concurrent              ( ThreadId )
import           Control.Concurrent.MVar         ( MVar )
import           Control.Monad.IO.Class          ( MonadIO )
import           Control.Monad.Reader            ( MonadReader, ReaderT )
import           Control.Monad.State             ( MonadState, StateT )
import           Data.IORef                      ( IORef )
import           Data.Typeable                   ( typeRep )
import           Control.Concurrent.STM          ( TVar )
import           Control.Exception               ( Exception )
import           Control.Monad.Reader            ( )
import           Data.Aeson                      ( (.:), (.:?), withObject, withText, object
                                                 , FromJSON(parseJSON), Value, KeyValue((.=))
                                                 , ToJSON(toJSON), genericParseJSON, defaultOptions
                                                 )
import           Data.Aeson.Types                ( Pair, typeMismatch, Parser )
import           Data.Proxy                      ( Proxy(Proxy) )
import           Data.String                     ( IsString(..) )
import           Data.Time                       ( UTCTime )
import           GHC.Generics                    ( Generic )
import           Network.Socket                  ( SockAddr )
import           System.IO                       ( Handle )
import           Text.Read                       ( readMaybe )
import           Data.Text                       (Text)
import qualified Data.Text                       as T ( pack, unpack , Text)
import qualified Data.HashMap.Strict             as H
import Colog.Core
import           DAP.Utils                       ( capitalize, getName, genericParseJSONWithModifier, genericToJSONWithModifier )
import DAP.Log
newtype Adaptor store r a =
    Adaptor (ExceptT (ErrorMessage, Maybe Message) (ReaderT (AdaptorLocal store r) (StateT AdaptorState IO)) a)
  deriving newtype
    ( Applicative (Adaptor store r)
Applicative (Adaptor store r) =>
(forall a b.
 Adaptor store r a -> (a -> Adaptor store r b) -> Adaptor store r b)
-> (forall a b.
    Adaptor store r a -> Adaptor store r b -> Adaptor store r b)
-> (forall a. a -> Adaptor store r a)
-> Monad (Adaptor store r)
forall a. a -> Adaptor store r a
forall store r. Applicative (Adaptor store r)
forall a b.
Adaptor store r a -> Adaptor store r b -> Adaptor store r b
forall a b.
Adaptor store r a -> (a -> Adaptor store r b) -> Adaptor store r b
forall store r a. a -> Adaptor store r a
forall store r a b.
Adaptor store r a -> Adaptor store r b -> Adaptor store r b
forall store r a b.
Adaptor store r a -> (a -> Adaptor store r b) -> Adaptor store r b
forall (m :: * -> *).
Applicative m =>
(forall a b. m a -> (a -> m b) -> m b)
-> (forall a b. m a -> m b -> m b)
-> (forall a. a -> m a)
-> Monad m
$c>>= :: forall store r a b.
Adaptor store r a -> (a -> Adaptor store r b) -> Adaptor store r b
>>= :: forall a b.
Adaptor store r a -> (a -> Adaptor store r b) -> Adaptor store r b
$c>> :: forall store r a b.
Adaptor store r a -> Adaptor store r b -> Adaptor store r b
>> :: forall a b.
Adaptor store r a -> Adaptor store r b -> Adaptor store r b
$creturn :: forall store r a. a -> Adaptor store r a
return :: forall a. a -> Adaptor store r a
Monad
    , Monad (Adaptor store r)
Monad (Adaptor store r) =>
(forall a. IO a -> Adaptor store r a) -> MonadIO (Adaptor store r)
forall a. IO a -> Adaptor store r a
forall store r. Monad (Adaptor store r)
forall store r a. IO a -> Adaptor store r a
forall (m :: * -> *).
Monad m =>
(forall a. IO a -> m a) -> MonadIO m
$cliftIO :: forall store r a. IO a -> Adaptor store r a
liftIO :: forall a. IO a -> Adaptor store r a
MonadIO, Functor (Adaptor store r)
Functor (Adaptor store r) =>
(forall a. a -> Adaptor store r a)
-> (forall a b.
    Adaptor store r (a -> b) -> Adaptor store r a -> Adaptor store r b)
-> (forall a b c.
    (a -> b -> c)
    -> Adaptor store r a -> Adaptor store r b -> Adaptor store r c)
-> (forall a b.
    Adaptor store r a -> Adaptor store r b -> Adaptor store r b)
-> (forall a b.
    Adaptor store r a -> Adaptor store r b -> Adaptor store r a)
-> Applicative (Adaptor store r)
forall a. a -> Adaptor store r a
forall store r. Functor (Adaptor store r)
forall a b.
Adaptor store r a -> Adaptor store r b -> Adaptor store r a
forall a b.
Adaptor store r a -> Adaptor store r b -> Adaptor store r b
forall a b.
Adaptor store r (a -> b) -> Adaptor store r a -> Adaptor store r b
forall store r a. a -> Adaptor store r a
forall a b c.
(a -> b -> c)
-> Adaptor store r a -> Adaptor store r b -> Adaptor store r c
forall store r a b.
Adaptor store r a -> Adaptor store r b -> Adaptor store r a
forall store r a b.
Adaptor store r a -> Adaptor store r b -> Adaptor store r b
forall store r a b.
Adaptor store r (a -> b) -> Adaptor store r a -> Adaptor store r b
forall store r a b c.
(a -> b -> c)
-> Adaptor store r a -> Adaptor store r b -> Adaptor store r c
forall (f :: * -> *).
Functor f =>
(forall a. a -> f a)
-> (forall a b. f (a -> b) -> f a -> f b)
-> (forall a b c. (a -> b -> c) -> f a -> f b -> f c)
-> (forall a b. f a -> f b -> f b)
-> (forall a b. f a -> f b -> f a)
-> Applicative f
$cpure :: forall store r a. a -> Adaptor store r a
pure :: forall a. a -> Adaptor store r a
$c<*> :: forall store r a b.
Adaptor store r (a -> b) -> Adaptor store r a -> Adaptor store r b
<*> :: forall a b.
Adaptor store r (a -> b) -> Adaptor store r a -> Adaptor store r b
$cliftA2 :: forall store r a b c.
(a -> b -> c)
-> Adaptor store r a -> Adaptor store r b -> Adaptor store r c
liftA2 :: forall a b c.
(a -> b -> c)
-> Adaptor store r a -> Adaptor store r b -> Adaptor store r c
$c*> :: forall store r a b.
Adaptor store r a -> Adaptor store r b -> Adaptor store r b
*> :: forall a b.
Adaptor store r a -> Adaptor store r b -> Adaptor store r b
$c<* :: forall store r a b.
Adaptor store r a -> Adaptor store r b -> Adaptor store r a
<* :: forall a b.
Adaptor store r a -> Adaptor store r b -> Adaptor store r a
Applicative, (forall a b. (a -> b) -> Adaptor store r a -> Adaptor store r b)
-> (forall a b. a -> Adaptor store r b -> Adaptor store r a)
-> Functor (Adaptor store r)
forall a b. a -> Adaptor store r b -> Adaptor store r a
forall a b. (a -> b) -> Adaptor store r a -> Adaptor store r b
forall store r a b. a -> Adaptor store r b -> Adaptor store r a
forall store r a b.
(a -> b) -> Adaptor store r a -> Adaptor store r b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
$cfmap :: forall store r a b.
(a -> b) -> Adaptor store r a -> Adaptor store r b
fmap :: forall a b. (a -> b) -> Adaptor store r a -> Adaptor store r b
$c<$ :: forall store r a b. a -> Adaptor store r b -> Adaptor store r a
<$ :: forall a b. a -> Adaptor store r b -> Adaptor store r a
Functor, MonadReader (AdaptorLocal store r)
    , MonadState AdaptorState
    , MonadBaseControl IO
    , MonadError (ErrorMessage, Maybe Message)
    , MonadBase IO
    )
data AdaptorState
  = AdaptorState
  { AdaptorState -> MessageType
messageType  :: MessageType
    
    
    
    
  , AdaptorState -> [Pair]
payload      :: ![Pair]
    
    
    
    
    
  }
data AdaptorLocal app request = AdaptorLocal
  { forall app request. AdaptorLocal app request -> AppStore app
appStore     :: AppStore app
    
    
    
  , forall app request. AdaptorLocal app request -> ServerConfig
serverConfig :: ServerConfig
    
    
    
  , forall app request. AdaptorLocal app request -> Handle
handle              :: Handle
    
    
    
  , forall app request. AdaptorLocal app request -> SockAddr
address             :: SockAddr
    
    
  , forall app request. AdaptorLocal app request -> IORef (Maybe Text)
sessionId           :: IORef (Maybe SessionId)
    
    
    
  , forall app request. AdaptorLocal app request -> MVar ()
handleLock          :: MVar ()
    
    
  , forall app request. AdaptorLocal app request -> LogAction IO DAPLog
logAction          :: LogAction IO DAPLog
    
    
  , forall app request. AdaptorLocal app request -> request
request             :: request
    
  }
type SessionId = Text
type AppStore app = TVar (H.HashMap SessionId (DebuggerThreadState, app))
data DebuggerThreadState
  = DebuggerThreadState
  { DebuggerThreadState -> [ThreadId]
debuggerThreads :: [ThreadId]
  }
data ServerConfig
  = ServerConfig
  { ServerConfig -> String
host               :: String
  , ServerConfig -> Int
port               :: Int
  , ServerConfig -> Capabilities
serverCapabilities :: Capabilities
  , ServerConfig -> Bool
debugLogging       :: Bool
  } deriving stock (Int -> ServerConfig -> ShowS
[ServerConfig] -> ShowS
ServerConfig -> String
(Int -> ServerConfig -> ShowS)
-> (ServerConfig -> String)
-> ([ServerConfig] -> ShowS)
-> Show ServerConfig
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ServerConfig -> ShowS
showsPrec :: Int -> ServerConfig -> ShowS
$cshow :: ServerConfig -> String
show :: ServerConfig -> String
$cshowList :: [ServerConfig] -> ShowS
showList :: [ServerConfig] -> ShowS
Show, ServerConfig -> ServerConfig -> Bool
(ServerConfig -> ServerConfig -> Bool)
-> (ServerConfig -> ServerConfig -> Bool) -> Eq ServerConfig
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ServerConfig -> ServerConfig -> Bool
== :: ServerConfig -> ServerConfig -> Bool
$c/= :: ServerConfig -> ServerConfig -> Bool
/= :: ServerConfig -> ServerConfig -> Bool
Eq)
data AdaptorException
  = ParseException String
  | ExpectedArguments T.Text
  | DebugSessionIdException T.Text
  | DebuggerException T.Text
  deriving stock (Int -> AdaptorException -> ShowS
[AdaptorException] -> ShowS
AdaptorException -> String
(Int -> AdaptorException -> ShowS)
-> (AdaptorException -> String)
-> ([AdaptorException] -> ShowS)
-> Show AdaptorException
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> AdaptorException -> ShowS
showsPrec :: Int -> AdaptorException -> ShowS
$cshow :: AdaptorException -> String
show :: AdaptorException -> String
$cshowList :: [AdaptorException] -> ShowS
showList :: [AdaptorException] -> ShowS
Show, AdaptorException -> AdaptorException -> Bool
(AdaptorException -> AdaptorException -> Bool)
-> (AdaptorException -> AdaptorException -> Bool)
-> Eq AdaptorException
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: AdaptorException -> AdaptorException -> Bool
== :: AdaptorException -> AdaptorException -> Bool
$c/= :: AdaptorException -> AdaptorException -> Bool
/= :: AdaptorException -> AdaptorException -> Bool
Eq)
  deriving anyclass Show AdaptorException
Typeable AdaptorException
(Typeable AdaptorException, Show AdaptorException) =>
(AdaptorException -> SomeException)
-> (SomeException -> Maybe AdaptorException)
-> (AdaptorException -> String)
-> Exception AdaptorException
SomeException -> Maybe AdaptorException
AdaptorException -> String
AdaptorException -> SomeException
forall e.
(Typeable e, Show e) =>
(e -> SomeException)
-> (SomeException -> Maybe e) -> (e -> String) -> Exception e
$ctoException :: AdaptorException -> SomeException
toException :: AdaptorException -> SomeException
$cfromException :: SomeException -> Maybe AdaptorException
fromException :: SomeException -> Maybe AdaptorException
$cdisplayException :: AdaptorException -> String
displayException :: AdaptorException -> String
Exception
type PayloadSize = Int
data MessageType
  = MessageTypeEvent
  | MessageTypeResponse
  | MessageTypeRequest
  deriving stock (Int -> MessageType -> ShowS
[MessageType] -> ShowS
MessageType -> String
(Int -> MessageType -> ShowS)
-> (MessageType -> String)
-> ([MessageType] -> ShowS)
-> Show MessageType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> MessageType -> ShowS
showsPrec :: Int -> MessageType -> ShowS
$cshow :: MessageType -> String
show :: MessageType -> String
$cshowList :: [MessageType] -> ShowS
showList :: [MessageType] -> ShowS
Show, MessageType -> MessageType -> Bool
(MessageType -> MessageType -> Bool)
-> (MessageType -> MessageType -> Bool) -> Eq MessageType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: MessageType -> MessageType -> Bool
== :: MessageType -> MessageType -> Bool
$c/= :: MessageType -> MessageType -> Bool
/= :: MessageType -> MessageType -> Bool
Eq, (forall x. MessageType -> Rep MessageType x)
-> (forall x. Rep MessageType x -> MessageType)
-> Generic MessageType
forall x. Rep MessageType x -> MessageType
forall x. MessageType -> Rep MessageType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. MessageType -> Rep MessageType x
from :: forall x. MessageType -> Rep MessageType x
$cto :: forall x. Rep MessageType x -> MessageType
to :: forall x. Rep MessageType x -> MessageType
Generic)
instance ToJSON MessageType where
  toJSON :: MessageType -> Value
toJSON = MessageType -> Value
forall a.
(Generic a, GToJSON Zero (Rep a), Typeable a) =>
a -> Value
genericToJSONWithModifier
type Seq = Int
data Request
  = Request
  { Request -> Maybe Value
args :: Maybe Value
    
    
  , Request -> Int
requestSeqNum :: Seq
    
    
  , Request -> Command
command :: Command
    
    
  } deriving stock (Int -> Request -> ShowS
[Request] -> ShowS
Request -> String
(Int -> Request -> ShowS)
-> (Request -> String) -> ([Request] -> ShowS) -> Show Request
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Request -> ShowS
showsPrec :: Int -> Request -> ShowS
$cshow :: Request -> String
show :: Request -> String
$cshowList :: [Request] -> ShowS
showList :: [Request] -> ShowS
Show)
instance FromJSON Request where
  parseJSON :: Value -> Parser Request
parseJSON = String -> (Object -> Parser Request) -> Value -> Parser Request
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"Request" ((Object -> Parser Request) -> Value -> Parser Request)
-> (Object -> Parser Request) -> Value -> Parser Request
forall a b. (a -> b) -> a -> b
$ \Object
o -> do
    String
"request" <- (Object
o Object -> Key -> Parser String
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"type") :: Parser String
    Maybe Value -> Int -> Command -> Request
Request
      (Maybe Value -> Int -> Command -> Request)
-> Parser (Maybe Value) -> Parser (Int -> Command -> Request)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser (Maybe Value)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"arguments"
      Parser (Int -> Command -> Request)
-> Parser Int -> Parser (Command -> Request)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser Int
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"seq"
      Parser (Command -> Request) -> Parser Command -> Parser Request
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser Command
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"command"
data ReverseRequestResponse
  = ReverseRequestResponse
  { ReverseRequestResponse -> Maybe Value
body :: Maybe Value
    
    
  , ReverseRequestResponse -> Int
reverseRequestResponseSeqNum :: Seq
    
    
  , ReverseRequestResponse -> ReverseCommand
reverseRequestCommand :: ReverseCommand
    
    
  , ReverseRequestResponse -> Bool
success :: Bool
    
  } deriving stock (Int -> ReverseRequestResponse -> ShowS
[ReverseRequestResponse] -> ShowS
ReverseRequestResponse -> String
(Int -> ReverseRequestResponse -> ShowS)
-> (ReverseRequestResponse -> String)
-> ([ReverseRequestResponse] -> ShowS)
-> Show ReverseRequestResponse
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ReverseRequestResponse -> ShowS
showsPrec :: Int -> ReverseRequestResponse -> ShowS
$cshow :: ReverseRequestResponse -> String
show :: ReverseRequestResponse -> String
$cshowList :: [ReverseRequestResponse] -> ShowS
showList :: [ReverseRequestResponse] -> ShowS
Show)
instance FromJSON ReverseRequestResponse where
  parseJSON :: Value -> Parser ReverseRequestResponse
parseJSON = String
-> (Object -> Parser ReverseRequestResponse)
-> Value
-> Parser ReverseRequestResponse
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"ReverseRequestResponse" ((Object -> Parser ReverseRequestResponse)
 -> Value -> Parser ReverseRequestResponse)
-> (Object -> Parser ReverseRequestResponse)
-> Value
-> Parser ReverseRequestResponse
forall a b. (a -> b) -> a -> b
$ \Object
o -> do
    String
"response" <- (Object
o Object -> Key -> Parser String
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"type") :: Parser String
    Maybe Value
-> Int -> ReverseCommand -> Bool -> ReverseRequestResponse
ReverseRequestResponse
      (Maybe Value
 -> Int -> ReverseCommand -> Bool -> ReverseRequestResponse)
-> Parser (Maybe Value)
-> Parser (Int -> ReverseCommand -> Bool -> ReverseRequestResponse)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser (Maybe Value)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"body"
      Parser (Int -> ReverseCommand -> Bool -> ReverseRequestResponse)
-> Parser Int
-> Parser (ReverseCommand -> Bool -> ReverseRequestResponse)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser Int
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"seq"
      Parser (ReverseCommand -> Bool -> ReverseRequestResponse)
-> Parser ReverseCommand -> Parser (Bool -> ReverseRequestResponse)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser ReverseCommand
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"command"
      Parser (Bool -> ReverseRequestResponse)
-> Parser Bool -> Parser ReverseRequestResponse
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser Bool
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"success"
data Breakpoint
  = Breakpoint
  { Breakpoint -> Maybe Int
breakpointId :: Maybe Int
    
    
    
    
  , Breakpoint -> Bool
breakpointVerified :: Bool
    
    
    
    
  , Breakpoint -> Maybe Text
breakpointMessage :: Maybe Text
    
    
    
    
    
  , Breakpoint -> Maybe Source
breakpointSource :: Maybe Source
    
    
    
  , Breakpoint -> Maybe Int
breakpointLine :: Maybe Int
    
    
    
  , Breakpoint -> Maybe Int
breakpointColumn :: Maybe Int
    
    
    
    
    
  , Breakpoint -> Maybe Int
breakpointEndLine :: Maybe Int
    
    
    
  , Breakpoint -> Maybe Int
breakpointEndColumn :: Maybe Int
    
    
    
    
    
    
    
  , Breakpoint -> Maybe Text
breakpointInstructionReference :: Maybe Text
    
    
    
  , Breakpoint -> Maybe Int
breakpointOffset :: Maybe Int
    
    
    
    
  } deriving stock (Int -> Breakpoint -> ShowS
[Breakpoint] -> ShowS
Breakpoint -> String
(Int -> Breakpoint -> ShowS)
-> (Breakpoint -> String)
-> ([Breakpoint] -> ShowS)
-> Show Breakpoint
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Breakpoint -> ShowS
showsPrec :: Int -> Breakpoint -> ShowS
$cshow :: Breakpoint -> String
show :: Breakpoint -> String
$cshowList :: [Breakpoint] -> ShowS
showList :: [Breakpoint] -> ShowS
Show, Breakpoint -> Breakpoint -> Bool
(Breakpoint -> Breakpoint -> Bool)
-> (Breakpoint -> Breakpoint -> Bool) -> Eq Breakpoint
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Breakpoint -> Breakpoint -> Bool
== :: Breakpoint -> Breakpoint -> Bool
$c/= :: Breakpoint -> Breakpoint -> Bool
/= :: Breakpoint -> Breakpoint -> Bool
Eq, (forall x. Breakpoint -> Rep Breakpoint x)
-> (forall x. Rep Breakpoint x -> Breakpoint) -> Generic Breakpoint
forall x. Rep Breakpoint x -> Breakpoint
forall x. Breakpoint -> Rep Breakpoint x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Breakpoint -> Rep Breakpoint x
from :: forall x. Breakpoint -> Rep Breakpoint x
$cto :: forall x. Rep Breakpoint x -> Breakpoint
to :: forall x. Rep Breakpoint x -> Breakpoint
Generic)
defaultBreakpoint :: Breakpoint
defaultBreakpoint :: Breakpoint
defaultBreakpoint = Breakpoint
  { breakpointId :: Maybe Int
breakpointId = Maybe Int
forall a. Maybe a
Nothing
  , breakpointVerified :: Bool
breakpointVerified = Bool
False
  , breakpointMessage :: Maybe Text
breakpointMessage = Maybe Text
forall a. Maybe a
Nothing
  , breakpointSource :: Maybe Source
breakpointSource = Maybe Source
forall a. Maybe a
Nothing
  , breakpointLine :: Maybe Int
breakpointLine = Maybe Int
forall a. Maybe a
Nothing
  , breakpointColumn :: Maybe Int
breakpointColumn = Maybe Int
forall a. Maybe a
Nothing
  , breakpointEndLine :: Maybe Int
breakpointEndLine = Maybe Int
forall a. Maybe a
Nothing
  , breakpointEndColumn :: Maybe Int
breakpointEndColumn = Maybe Int
forall a. Maybe a
Nothing
  , breakpointInstructionReference :: Maybe Text
breakpointInstructionReference = Maybe Text
forall a. Maybe a
Nothing
  , breakpointOffset :: Maybe Int
breakpointOffset = Maybe Int
forall a. Maybe a
Nothing
  }
instance ToJSON Breakpoint where
  toJSON :: Breakpoint -> Value
toJSON = Breakpoint -> Value
forall a.
(Generic a, GToJSON Zero (Rep a), Typeable a) =>
a -> Value
genericToJSONWithModifier
newtype Breakpoints breakpoint = Breakpoints [breakpoint]
  deriving stock (Int -> Breakpoints breakpoint -> ShowS
[Breakpoints breakpoint] -> ShowS
Breakpoints breakpoint -> String
(Int -> Breakpoints breakpoint -> ShowS)
-> (Breakpoints breakpoint -> String)
-> ([Breakpoints breakpoint] -> ShowS)
-> Show (Breakpoints breakpoint)
forall breakpoint.
Show breakpoint =>
Int -> Breakpoints breakpoint -> ShowS
forall breakpoint.
Show breakpoint =>
[Breakpoints breakpoint] -> ShowS
forall breakpoint.
Show breakpoint =>
Breakpoints breakpoint -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall breakpoint.
Show breakpoint =>
Int -> Breakpoints breakpoint -> ShowS
showsPrec :: Int -> Breakpoints breakpoint -> ShowS
$cshow :: forall breakpoint.
Show breakpoint =>
Breakpoints breakpoint -> String
show :: Breakpoints breakpoint -> String
$cshowList :: forall breakpoint.
Show breakpoint =>
[Breakpoints breakpoint] -> ShowS
showList :: [Breakpoints breakpoint] -> ShowS
Show, Breakpoints breakpoint -> Breakpoints breakpoint -> Bool
(Breakpoints breakpoint -> Breakpoints breakpoint -> Bool)
-> (Breakpoints breakpoint -> Breakpoints breakpoint -> Bool)
-> Eq (Breakpoints breakpoint)
forall breakpoint.
Eq breakpoint =>
Breakpoints breakpoint -> Breakpoints breakpoint -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall breakpoint.
Eq breakpoint =>
Breakpoints breakpoint -> Breakpoints breakpoint -> Bool
== :: Breakpoints breakpoint -> Breakpoints breakpoint -> Bool
$c/= :: forall breakpoint.
Eq breakpoint =>
Breakpoints breakpoint -> Breakpoints breakpoint -> Bool
/= :: Breakpoints breakpoint -> Breakpoints breakpoint -> Bool
Eq)
instance ToJSON breakpoint => ToJSON (Breakpoints breakpoint) where
  toJSON :: Breakpoints breakpoint -> Value
toJSON (Breakpoints [breakpoint]
breakpoints)
    = [Pair] -> Value
object
    [ Key
"breakpoints" Key -> [breakpoint] -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= [breakpoint]
breakpoints
    ]
data Source
  = Source
  { Source -> Maybe Text
sourceName :: Maybe Text
    
    
    
    
    
  , Source -> Maybe Text
sourcePath :: Maybe Text
    
    
    
    
    
  , Source -> Maybe Int
sourceSourceReference :: Maybe Int
    
    
    
    
    
    
    
  , Source -> Maybe SourcePresentationHint
sourcePresentationHint :: Maybe SourcePresentationHint
    
    
    
    
    
    
  , Source -> Maybe Text
sourceOrigin :: Maybe Text
    
    
    
    
  , Source -> Maybe [Source]
sourceSources :: Maybe [Source]
    
    
    
    
  , Source -> Maybe Value
sourceAdapterData :: Maybe Value
    
    
    
    
    
  , Source -> Maybe [Checksum]
sourceChecksums :: Maybe [Checksum]
    
    
    
  } deriving stock (Int -> Source -> ShowS
[Source] -> ShowS
Source -> String
(Int -> Source -> ShowS)
-> (Source -> String) -> ([Source] -> ShowS) -> Show Source
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Source -> ShowS
showsPrec :: Int -> Source -> ShowS
$cshow :: Source -> String
show :: Source -> String
$cshowList :: [Source] -> ShowS
showList :: [Source] -> ShowS
Show, Source -> Source -> Bool
(Source -> Source -> Bool)
-> (Source -> Source -> Bool) -> Eq Source
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Source -> Source -> Bool
== :: Source -> Source -> Bool
$c/= :: Source -> Source -> Bool
/= :: Source -> Source -> Bool
Eq, (forall x. Source -> Rep Source x)
-> (forall x. Rep Source x -> Source) -> Generic Source
forall x. Rep Source x -> Source
forall x. Source -> Rep Source x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Source -> Rep Source x
from :: forall x. Source -> Rep Source x
$cto :: forall x. Rep Source x -> Source
to :: forall x. Rep Source x -> Source
Generic)
defaultSource :: Source
defaultSource :: Source
defaultSource
  = Source
  { sourceName :: Maybe Text
sourceName             = Maybe Text
forall a. Maybe a
Nothing
  , sourcePath :: Maybe Text
sourcePath             = Maybe Text
forall a. Maybe a
Nothing
  , sourceSourceReference :: Maybe Int
sourceSourceReference  = Maybe Int
forall a. Maybe a
Nothing
  , sourcePresentationHint :: Maybe SourcePresentationHint
sourcePresentationHint = Maybe SourcePresentationHint
forall a. Maybe a
Nothing
  , sourceOrigin :: Maybe Text
sourceOrigin           = Maybe Text
forall a. Maybe a
Nothing
  , sourceSources :: Maybe [Source]
sourceSources          = Maybe [Source]
forall a. Maybe a
Nothing
  , sourceAdapterData :: Maybe Value
sourceAdapterData      = Maybe Value
forall a. Maybe a
Nothing
  , sourceChecksums :: Maybe [Checksum]
sourceChecksums        = Maybe [Checksum]
forall a. Maybe a
Nothing
  }
instance FromJSON Source where
   parseJSON :: Value -> Parser Source
parseJSON = Value -> Parser Source
forall a.
(Generic a, GFromJSON Zero (Rep a), Typeable a) =>
Value -> Parser a
genericParseJSONWithModifier
instance ToJSON Source where
  toJSON :: Source -> Value
toJSON = Source -> Value
forall a.
(Generic a, GToJSON Zero (Rep a), Typeable a) =>
a -> Value
genericToJSONWithModifier
newtype Sources = Sources { Sources -> [Source]
getSources :: [Source] } deriving stock (Int -> Sources -> ShowS
[Sources] -> ShowS
Sources -> String
(Int -> Sources -> ShowS)
-> (Sources -> String) -> ([Sources] -> ShowS) -> Show Sources
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Sources -> ShowS
showsPrec :: Int -> Sources -> ShowS
$cshow :: Sources -> String
show :: Sources -> String
$cshowList :: [Sources] -> ShowS
showList :: [Sources] -> ShowS
Show, Sources -> Sources -> Bool
(Sources -> Sources -> Bool)
-> (Sources -> Sources -> Bool) -> Eq Sources
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Sources -> Sources -> Bool
== :: Sources -> Sources -> Bool
$c/= :: Sources -> Sources -> Bool
/= :: Sources -> Sources -> Bool
Eq)
instance ToJSON Sources where toJSON :: Sources -> Value
toJSON (Sources [Source]
s) = [Pair] -> Value
object [ Key
"sources" Key -> [Source] -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= [Source]
s ]
data SourcePresentationHint
  = SourcePresentationHintNormal
  | SourcePresentationHintEmphasize
  | SourcePresentationHintDeemphasize
  deriving stock (Int -> SourcePresentationHint -> ShowS
[SourcePresentationHint] -> ShowS
SourcePresentationHint -> String
(Int -> SourcePresentationHint -> ShowS)
-> (SourcePresentationHint -> String)
-> ([SourcePresentationHint] -> ShowS)
-> Show SourcePresentationHint
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SourcePresentationHint -> ShowS
showsPrec :: Int -> SourcePresentationHint -> ShowS
$cshow :: SourcePresentationHint -> String
show :: SourcePresentationHint -> String
$cshowList :: [SourcePresentationHint] -> ShowS
showList :: [SourcePresentationHint] -> ShowS
Show, SourcePresentationHint -> SourcePresentationHint -> Bool
(SourcePresentationHint -> SourcePresentationHint -> Bool)
-> (SourcePresentationHint -> SourcePresentationHint -> Bool)
-> Eq SourcePresentationHint
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SourcePresentationHint -> SourcePresentationHint -> Bool
== :: SourcePresentationHint -> SourcePresentationHint -> Bool
$c/= :: SourcePresentationHint -> SourcePresentationHint -> Bool
/= :: SourcePresentationHint -> SourcePresentationHint -> Bool
Eq, (forall x. SourcePresentationHint -> Rep SourcePresentationHint x)
-> (forall x.
    Rep SourcePresentationHint x -> SourcePresentationHint)
-> Generic SourcePresentationHint
forall x. Rep SourcePresentationHint x -> SourcePresentationHint
forall x. SourcePresentationHint -> Rep SourcePresentationHint x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. SourcePresentationHint -> Rep SourcePresentationHint x
from :: forall x. SourcePresentationHint -> Rep SourcePresentationHint x
$cto :: forall x. Rep SourcePresentationHint x -> SourcePresentationHint
to :: forall x. Rep SourcePresentationHint x -> SourcePresentationHint
Generic)
instance FromJSON SourcePresentationHint where
   parseJSON :: Value -> Parser SourcePresentationHint
parseJSON = Value -> Parser SourcePresentationHint
forall a.
(Generic a, GFromJSON Zero (Rep a), Typeable a) =>
Value -> Parser a
genericParseJSONWithModifier
instance ToJSON SourcePresentationHint where
  toJSON :: SourcePresentationHint -> Value
toJSON = SourcePresentationHint -> Value
forall a.
(Generic a, GToJSON Zero (Rep a), Typeable a) =>
a -> Value
genericToJSONWithModifier
data PresentationHint
  = PresentationHintNormal
  | PresentationHintLabel
  | PresentationHintSubtle
  deriving stock (Int -> PresentationHint -> ShowS
[PresentationHint] -> ShowS
PresentationHint -> String
(Int -> PresentationHint -> ShowS)
-> (PresentationHint -> String)
-> ([PresentationHint] -> ShowS)
-> Show PresentationHint
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> PresentationHint -> ShowS
showsPrec :: Int -> PresentationHint -> ShowS
$cshow :: PresentationHint -> String
show :: PresentationHint -> String
$cshowList :: [PresentationHint] -> ShowS
showList :: [PresentationHint] -> ShowS
Show, PresentationHint -> PresentationHint -> Bool
(PresentationHint -> PresentationHint -> Bool)
-> (PresentationHint -> PresentationHint -> Bool)
-> Eq PresentationHint
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: PresentationHint -> PresentationHint -> Bool
== :: PresentationHint -> PresentationHint -> Bool
$c/= :: PresentationHint -> PresentationHint -> Bool
/= :: PresentationHint -> PresentationHint -> Bool
Eq, (forall x. PresentationHint -> Rep PresentationHint x)
-> (forall x. Rep PresentationHint x -> PresentationHint)
-> Generic PresentationHint
forall x. Rep PresentationHint x -> PresentationHint
forall x. PresentationHint -> Rep PresentationHint x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. PresentationHint -> Rep PresentationHint x
from :: forall x. PresentationHint -> Rep PresentationHint x
$cto :: forall x. Rep PresentationHint x -> PresentationHint
to :: forall x. Rep PresentationHint x -> PresentationHint
Generic)
instance ToJSON PresentationHint where
  toJSON :: PresentationHint -> Value
toJSON = PresentationHint -> Value
forall a.
(Generic a, GToJSON Zero (Rep a), Typeable a) =>
a -> Value
genericToJSONWithModifier
data Checksum
  = Checksum
  { Checksum -> ChecksumAlgorithm
algorithm :: ChecksumAlgorithm
    
    
  , Checksum -> Text
checksum :: Text
    
    
  } deriving stock (Int -> Checksum -> ShowS
[Checksum] -> ShowS
Checksum -> String
(Int -> Checksum -> ShowS)
-> (Checksum -> String) -> ([Checksum] -> ShowS) -> Show Checksum
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Checksum -> ShowS
showsPrec :: Int -> Checksum -> ShowS
$cshow :: Checksum -> String
show :: Checksum -> String
$cshowList :: [Checksum] -> ShowS
showList :: [Checksum] -> ShowS
Show, Checksum -> Checksum -> Bool
(Checksum -> Checksum -> Bool)
-> (Checksum -> Checksum -> Bool) -> Eq Checksum
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Checksum -> Checksum -> Bool
== :: Checksum -> Checksum -> Bool
$c/= :: Checksum -> Checksum -> Bool
/= :: Checksum -> Checksum -> Bool
Eq, (forall x. Checksum -> Rep Checksum x)
-> (forall x. Rep Checksum x -> Checksum) -> Generic Checksum
forall x. Rep Checksum x -> Checksum
forall x. Checksum -> Rep Checksum x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Checksum -> Rep Checksum x
from :: forall x. Checksum -> Rep Checksum x
$cto :: forall x. Rep Checksum x -> Checksum
to :: forall x. Rep Checksum x -> Checksum
Generic)
    deriving anyclass ([Checksum] -> Value
[Checksum] -> Encoding
Checksum -> Bool
Checksum -> Value
Checksum -> Encoding
(Checksum -> Value)
-> (Checksum -> Encoding)
-> ([Checksum] -> Value)
-> ([Checksum] -> Encoding)
-> (Checksum -> Bool)
-> ToJSON Checksum
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: Checksum -> Value
toJSON :: Checksum -> Value
$ctoEncoding :: Checksum -> Encoding
toEncoding :: Checksum -> Encoding
$ctoJSONList :: [Checksum] -> Value
toJSONList :: [Checksum] -> Value
$ctoEncodingList :: [Checksum] -> Encoding
toEncodingList :: [Checksum] -> Encoding
$comitField :: Checksum -> Bool
omitField :: Checksum -> Bool
ToJSON, Maybe Checksum
Value -> Parser [Checksum]
Value -> Parser Checksum
(Value -> Parser Checksum)
-> (Value -> Parser [Checksum])
-> Maybe Checksum
-> FromJSON Checksum
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser Checksum
parseJSON :: Value -> Parser Checksum
$cparseJSONList :: Value -> Parser [Checksum]
parseJSONList :: Value -> Parser [Checksum]
$comittedField :: Maybe Checksum
omittedField :: Maybe Checksum
FromJSON)
data ChecksumAlgorithm
  = MD5
  | SHA1
  | SHA256
  | TimeStamp UTCTime
  deriving stock (Int -> ChecksumAlgorithm -> ShowS
[ChecksumAlgorithm] -> ShowS
ChecksumAlgorithm -> String
(Int -> ChecksumAlgorithm -> ShowS)
-> (ChecksumAlgorithm -> String)
-> ([ChecksumAlgorithm] -> ShowS)
-> Show ChecksumAlgorithm
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ChecksumAlgorithm -> ShowS
showsPrec :: Int -> ChecksumAlgorithm -> ShowS
$cshow :: ChecksumAlgorithm -> String
show :: ChecksumAlgorithm -> String
$cshowList :: [ChecksumAlgorithm] -> ShowS
showList :: [ChecksumAlgorithm] -> ShowS
Show, ChecksumAlgorithm -> ChecksumAlgorithm -> Bool
(ChecksumAlgorithm -> ChecksumAlgorithm -> Bool)
-> (ChecksumAlgorithm -> ChecksumAlgorithm -> Bool)
-> Eq ChecksumAlgorithm
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ChecksumAlgorithm -> ChecksumAlgorithm -> Bool
== :: ChecksumAlgorithm -> ChecksumAlgorithm -> Bool
$c/= :: ChecksumAlgorithm -> ChecksumAlgorithm -> Bool
/= :: ChecksumAlgorithm -> ChecksumAlgorithm -> Bool
Eq)
instance ToJSON ChecksumAlgorithm where
  toJSON :: ChecksumAlgorithm -> Value
toJSON ChecksumAlgorithm
MD5                 = Value
"md5"
  toJSON ChecksumAlgorithm
SHA1                = Value
"sha1"
  toJSON ChecksumAlgorithm
SHA256              = Value
"sha256"
  toJSON (TimeStamp UTCTime
utcTime) = UTCTime -> Value
forall a. ToJSON a => a -> Value
toJSON UTCTime
utcTime
instance FromJSON ChecksumAlgorithm where
  parseJSON :: Value -> Parser ChecksumAlgorithm
parseJSON = String
-> (Text -> Parser ChecksumAlgorithm)
-> Value
-> Parser ChecksumAlgorithm
forall a. String -> (Text -> Parser a) -> Value -> Parser a
withText String
name ((Text -> Parser ChecksumAlgorithm)
 -> Value -> Parser ChecksumAlgorithm)
-> (Text -> Parser ChecksumAlgorithm)
-> Value
-> Parser ChecksumAlgorithm
forall a b. (a -> b) -> a -> b
$ \Text
txt ->
    case Text
txt of
      Text
"md5" -> ChecksumAlgorithm -> Parser ChecksumAlgorithm
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ChecksumAlgorithm
MD5
      Text
"sha1" -> ChecksumAlgorithm -> Parser ChecksumAlgorithm
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ChecksumAlgorithm
SHA1
      Text
"sha256" -> ChecksumAlgorithm -> Parser ChecksumAlgorithm
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ChecksumAlgorithm
SHA256
      Text
s -> String -> Value -> Parser ChecksumAlgorithm
forall a. String -> Value -> Parser a
typeMismatch String
name (Text -> Value
forall a. ToJSON a => a -> Value
toJSON Text
s)
    where
      name :: String
name = Proxy ChecksumAlgorithm -> String
forall a (proxy :: * -> *). Typeable a => proxy a -> String
getName (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @ChecksumAlgorithm)
data StackFrame
  = StackFrame
  { StackFrame -> Int
stackFrameId :: Int
    
    
    
    
    
  , StackFrame -> Text
stackFrameName :: Text
    
    
    
  , StackFrame -> Maybe Source
stackFrameSource :: Maybe Source
    
    
    
  , StackFrame -> Int
stackFrameLine :: Int
    
    
    
    
  , StackFrame -> Int
stackFrameColumn :: Int
    
    
    
    
    
    
  , StackFrame -> Maybe Int
stackFrameEndLine :: Maybe Int
    
    
    
  , StackFrame -> Maybe Int
stackFrameEndColumn :: Maybe Int
    
    
    
    
    
  , StackFrame -> Maybe Bool
stackFrameCanRestart :: Maybe Bool
    
    
    
    
    
    
    
  , StackFrame -> Maybe Text
stackFrameInstructionPointerReference :: Maybe Text
    
    
    
  , StackFrame -> Maybe (Either Int Text)
stackFrameModuleId :: Maybe (Either Int Text)
    
    
    
  , StackFrame -> Maybe PresentationHint
stackFramePresentationHint :: Maybe PresentationHint
    
    
    
    
    
    
    
  } deriving stock (Int -> StackFrame -> ShowS
[StackFrame] -> ShowS
StackFrame -> String
(Int -> StackFrame -> ShowS)
-> (StackFrame -> String)
-> ([StackFrame] -> ShowS)
-> Show StackFrame
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> StackFrame -> ShowS
showsPrec :: Int -> StackFrame -> ShowS
$cshow :: StackFrame -> String
show :: StackFrame -> String
$cshowList :: [StackFrame] -> ShowS
showList :: [StackFrame] -> ShowS
Show, StackFrame -> StackFrame -> Bool
(StackFrame -> StackFrame -> Bool)
-> (StackFrame -> StackFrame -> Bool) -> Eq StackFrame
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: StackFrame -> StackFrame -> Bool
== :: StackFrame -> StackFrame -> Bool
$c/= :: StackFrame -> StackFrame -> Bool
/= :: StackFrame -> StackFrame -> Bool
Eq, (forall x. StackFrame -> Rep StackFrame x)
-> (forall x. Rep StackFrame x -> StackFrame) -> Generic StackFrame
forall x. Rep StackFrame x -> StackFrame
forall x. StackFrame -> Rep StackFrame x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. StackFrame -> Rep StackFrame x
from :: forall x. StackFrame -> Rep StackFrame x
$cto :: forall x. Rep StackFrame x -> StackFrame
to :: forall x. Rep StackFrame x -> StackFrame
Generic)
defaultStackFrame :: StackFrame
defaultStackFrame :: StackFrame
defaultStackFrame
  = StackFrame
  { stackFrameId :: Int
stackFrameId = Int
0
  , stackFrameName :: Text
stackFrameName = Text
forall a. Monoid a => a
mempty
  , stackFrameSource :: Maybe Source
stackFrameSource = Maybe Source
forall a. Maybe a
Nothing
  , stackFrameLine :: Int
stackFrameLine = Int
0
  , stackFrameColumn :: Int
stackFrameColumn = Int
0
  , stackFrameEndLine :: Maybe Int
stackFrameEndLine = Maybe Int
forall a. Maybe a
Nothing
  , stackFrameEndColumn :: Maybe Int
stackFrameEndColumn = Maybe Int
forall a. Maybe a
Nothing
  , stackFrameCanRestart :: Maybe Bool
stackFrameCanRestart = Maybe Bool
forall a. Maybe a
Nothing
  , stackFrameInstructionPointerReference :: Maybe Text
stackFrameInstructionPointerReference = Maybe Text
forall a. Maybe a
Nothing
  , stackFrameModuleId :: Maybe (Either Int Text)
stackFrameModuleId = Maybe (Either Int Text)
forall a. Maybe a
Nothing
  , stackFramePresentationHint :: Maybe PresentationHint
stackFramePresentationHint = Maybe PresentationHint
forall a. Maybe a
Nothing
  }
instance ToJSON StackFrame where
  toJSON :: StackFrame -> Value
toJSON = StackFrame -> Value
forall a.
(Generic a, GToJSON Zero (Rep a), Typeable a) =>
a -> Value
genericToJSONWithModifier
data Thread
  = Thread
  { Thread -> Int
threadId :: Int
    
    
  , Thread -> Text
threadName :: Text
    
    
  } deriving stock (Int -> Thread -> ShowS
[Thread] -> ShowS
Thread -> String
(Int -> Thread -> ShowS)
-> (Thread -> String) -> ([Thread] -> ShowS) -> Show Thread
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Thread -> ShowS
showsPrec :: Int -> Thread -> ShowS
$cshow :: Thread -> String
show :: Thread -> String
$cshowList :: [Thread] -> ShowS
showList :: [Thread] -> ShowS
Show, Thread -> Thread -> Bool
(Thread -> Thread -> Bool)
-> (Thread -> Thread -> Bool) -> Eq Thread
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Thread -> Thread -> Bool
== :: Thread -> Thread -> Bool
$c/= :: Thread -> Thread -> Bool
/= :: Thread -> Thread -> Bool
Eq, (forall x. Thread -> Rep Thread x)
-> (forall x. Rep Thread x -> Thread) -> Generic Thread
forall x. Rep Thread x -> Thread
forall x. Thread -> Rep Thread x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Thread -> Rep Thread x
from :: forall x. Thread -> Rep Thread x
$cto :: forall x. Rep Thread x -> Thread
to :: forall x. Rep Thread x -> Thread
Generic)
defaultThread :: Thread
defaultThread :: Thread
defaultThread
  = Thread
  { threadId :: Int
threadId = Int
0
  , threadName :: Text
threadName = Text
"<main>"
  }
instance ToJSON Thread where
  toJSON :: Thread -> Value
toJSON = Thread -> Value
forall a.
(Generic a, GToJSON Zero (Rep a), Typeable a) =>
a -> Value
genericToJSONWithModifier
instance FromJSON Thread where
  parseJSON :: Value -> Parser Thread
parseJSON = Value -> Parser Thread
forall a.
(Generic a, GFromJSON Zero (Rep a), Typeable a) =>
Value -> Parser a
genericParseJSONWithModifier
defaultCapabilities :: Capabilities
defaultCapabilities :: Capabilities
defaultCapabilities = Capabilities
capabilities
  where
    capabilities :: Capabilities
capabilities = Capabilities
      { supportsConfigurationDoneRequest :: Bool
supportsConfigurationDoneRequest      = Bool
False
      , supportsFunctionBreakpoints :: Bool
supportsFunctionBreakpoints           = Bool
False
      , supportsConditionalBreakpoints :: Bool
supportsConditionalBreakpoints        = Bool
False
      , supportsHitConditionalBreakpoints :: Bool
supportsHitConditionalBreakpoints     = Bool
False
      , supportsEvaluateForHovers :: Bool
supportsEvaluateForHovers             = Bool
False
      , exceptionBreakpointFilters :: [ExceptionBreakpointsFilter]
exceptionBreakpointFilters            = []
      , supportsStepBack :: Bool
supportsStepBack                      = Bool
False
      , supportsSetVariable :: Bool
supportsSetVariable                   = Bool
False
      , supportsRestartFrame :: Bool
supportsRestartFrame                  = Bool
False
      , supportsGotoTargetsRequest :: Bool
supportsGotoTargetsRequest            = Bool
False
      , supportsStepInTargetsRequest :: Bool
supportsStepInTargetsRequest          = Bool
False
      , supportsCompletionsRequest :: Bool
supportsCompletionsRequest            = Bool
False
      , completionTriggerCharacters :: [Text]
completionTriggerCharacters           = []
      , supportsModulesRequest :: Bool
supportsModulesRequest                = Bool
False
      , additionalModuleColumns :: [ColumnDescriptor]
additionalModuleColumns               = []
      , supportedChecksumAlgorithms :: [ChecksumAlgorithm]
supportedChecksumAlgorithms           = []
      , supportsRestartRequest :: Bool
supportsRestartRequest                = Bool
False
      , supportsExceptionOptions :: Bool
supportsExceptionOptions              = Bool
False
      , supportsValueFormattingOptions :: Bool
supportsValueFormattingOptions        = Bool
False
      , supportsExceptionInfoRequest :: Bool
supportsExceptionInfoRequest          = Bool
False
      , supportTerminateDebuggee :: Bool
supportTerminateDebuggee              = Bool
False
      , supportSuspendDebuggee :: Bool
supportSuspendDebuggee                = Bool
False
      , supportsDelayedStackTraceLoading :: Bool
supportsDelayedStackTraceLoading      = Bool
False
      , supportsLoadedSourcesRequest :: Bool
supportsLoadedSourcesRequest          = Bool
False
      , supportsLogPoints :: Bool
supportsLogPoints                     = Bool
False
      , supportsTerminateThreadsRequest :: Bool
supportsTerminateThreadsRequest       = Bool
False
      , supportsSetExpression :: Bool
supportsSetExpression                 = Bool
False
      , supportsTerminateRequest :: Bool
supportsTerminateRequest              = Bool
False
      , supportsDataBreakpoints :: Bool
supportsDataBreakpoints               = Bool
False
      , supportsReadMemoryRequest :: Bool
supportsReadMemoryRequest             = Bool
False
      , supportsWriteMemoryRequest :: Bool
supportsWriteMemoryRequest            = Bool
False
      , supportsDisassembleRequest :: Bool
supportsDisassembleRequest            = Bool
False
      , supportsCancelRequest :: Bool
supportsCancelRequest                 = Bool
False
      , supportsBreakpointLocationsRequest :: Bool
supportsBreakpointLocationsRequest    = Bool
False
      , supportsClipboardContext :: Bool
supportsClipboardContext              = Bool
False
      , supportsSteppingGranularity :: Bool
supportsSteppingGranularity           = Bool
False
      , supportsInstructionBreakpoints :: Bool
supportsInstructionBreakpoints        = Bool
False
      , supportsExceptionFilterOptions :: Bool
supportsExceptionFilterOptions        = Bool
False
      , supportsSingleThreadExecutionRequests :: Bool
supportsSingleThreadExecutionRequests = Bool
False
      }
data Capabilities
  = Capabilities
  { Capabilities -> Bool
supportsConfigurationDoneRequest :: Bool
    
    
  , Capabilities -> Bool
supportsFunctionBreakpoints :: Bool
    
    
  , Capabilities -> Bool
supportsConditionalBreakpoints :: Bool
    
    
  , Capabilities -> Bool
supportsHitConditionalBreakpoints :: Bool
    
    
    
  , Capabilities -> Bool
supportsEvaluateForHovers :: Bool
    
    
    
  , Capabilities -> [ExceptionBreakpointsFilter]
exceptionBreakpointFilters :: [ExceptionBreakpointsFilter]
    
    
    
  , Capabilities -> Bool
supportsStepBack :: Bool
    
    
    
  , Capabilities -> Bool
supportsSetVariable :: Bool
    
    
  , Capabilities -> Bool
supportsRestartFrame :: Bool
    
    
  , Capabilities -> Bool
supportsGotoTargetsRequest :: Bool
    
    
  , Capabilities -> Bool
supportsStepInTargetsRequest :: Bool
    
    
  , Capabilities -> Bool
supportsCompletionsRequest :: Bool
    
    
  , Capabilities -> [Text]
completionTriggerCharacters :: [Text]
    
    
    
  , Capabilities -> Bool
supportsModulesRequest :: Bool
    
    
  , Capabilities -> [ColumnDescriptor]
additionalModuleColumns :: [ColumnDescriptor]
    
    
  , Capabilities -> [ChecksumAlgorithm]
supportedChecksumAlgorithms :: [ChecksumAlgorithm]
    
    
  , Capabilities -> Bool
supportsRestartRequest :: Bool
    
    
    
    
  , Capabilities -> Bool
supportsExceptionOptions :: Bool
    
    
    
  , Capabilities -> Bool
supportsValueFormattingOptions :: Bool
    
    
    
  , Capabilities -> Bool
supportsExceptionInfoRequest :: Bool
    
    
  , Capabilities -> Bool
supportTerminateDebuggee :: Bool
    
    
  , Capabilities -> Bool
supportSuspendDebuggee :: Bool
    
    
  , Capabilities -> Bool
supportsDelayedStackTraceLoading :: Bool
    
    
    
    
  , Capabilities -> Bool
supportsLoadedSourcesRequest :: Bool
    
    
  , Capabilities -> Bool
supportsLogPoints :: Bool
    
    
    
  , Capabilities -> Bool
supportsTerminateThreadsRequest :: Bool
    
    
  , Capabilities -> Bool
supportsSetExpression :: Bool
    
    
  , Capabilities -> Bool
supportsTerminateRequest :: Bool
    
    
  , Capabilities -> Bool
supportsDataBreakpoints :: Bool
    
    
  , Capabilities -> Bool
supportsReadMemoryRequest :: Bool
    
    
  , Capabilities -> Bool
supportsWriteMemoryRequest :: Bool
    
    
  , Capabilities -> Bool
supportsDisassembleRequest :: Bool
    
    
  , Capabilities -> Bool
supportsCancelRequest :: Bool
    
    
  , Capabilities -> Bool
supportsBreakpointLocationsRequest :: Bool
    
    
  , Capabilities -> Bool
supportsClipboardContext :: Bool
    
    
    
  , Capabilities -> Bool
supportsSteppingGranularity :: Bool
    
    
    
  , Capabilities -> Bool
supportsInstructionBreakpoints :: Bool
    
    
    
  , Capabilities -> Bool
supportsExceptionFilterOptions :: Bool
    
    
    
  , Capabilities -> Bool
supportsSingleThreadExecutionRequests :: Bool
    
    
    
    
  } deriving stock (Int -> Capabilities -> ShowS
[Capabilities] -> ShowS
Capabilities -> String
(Int -> Capabilities -> ShowS)
-> (Capabilities -> String)
-> ([Capabilities] -> ShowS)
-> Show Capabilities
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Capabilities -> ShowS
showsPrec :: Int -> Capabilities -> ShowS
$cshow :: Capabilities -> String
show :: Capabilities -> String
$cshowList :: [Capabilities] -> ShowS
showList :: [Capabilities] -> ShowS
Show, Capabilities -> Capabilities -> Bool
(Capabilities -> Capabilities -> Bool)
-> (Capabilities -> Capabilities -> Bool) -> Eq Capabilities
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Capabilities -> Capabilities -> Bool
== :: Capabilities -> Capabilities -> Bool
$c/= :: Capabilities -> Capabilities -> Bool
/= :: Capabilities -> Capabilities -> Bool
Eq, (forall x. Capabilities -> Rep Capabilities x)
-> (forall x. Rep Capabilities x -> Capabilities)
-> Generic Capabilities
forall x. Rep Capabilities x -> Capabilities
forall x. Capabilities -> Rep Capabilities x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Capabilities -> Rep Capabilities x
from :: forall x. Capabilities -> Rep Capabilities x
$cto :: forall x. Rep Capabilities x -> Capabilities
to :: forall x. Rep Capabilities x -> Capabilities
Generic)
    deriving anyclass ([Capabilities] -> Value
[Capabilities] -> Encoding
Capabilities -> Bool
Capabilities -> Value
Capabilities -> Encoding
(Capabilities -> Value)
-> (Capabilities -> Encoding)
-> ([Capabilities] -> Value)
-> ([Capabilities] -> Encoding)
-> (Capabilities -> Bool)
-> ToJSON Capabilities
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: Capabilities -> Value
toJSON :: Capabilities -> Value
$ctoEncoding :: Capabilities -> Encoding
toEncoding :: Capabilities -> Encoding
$ctoJSONList :: [Capabilities] -> Value
toJSONList :: [Capabilities] -> Value
$ctoEncodingList :: [Capabilities] -> Encoding
toEncodingList :: [Capabilities] -> Encoding
$comitField :: Capabilities -> Bool
omitField :: Capabilities -> Bool
ToJSON)
data EventType
  = EventTypeInitialized
  | EventTypeStopped
  | EventTypeContinued
  | EventTypeExited
  | EventTypeTerminated
  | EventTypeThread
  | EventTypeOutput
  | EventTypeBreakpoint
  | EventTypeModule
  | EventTypeLoadedSource
  | EventTypeProcess
  | EventTypeCapabilities
  | EventTypeProgressStart
  | EventTypeProgressUpdate
  | EventTypeProgressEnd
  | EventTypeInvalidated
  | EventTypeMemory
  | EventTypeCustom Text
  deriving stock (Int -> EventType -> ShowS
[EventType] -> ShowS
EventType -> String
(Int -> EventType -> ShowS)
-> (EventType -> String)
-> ([EventType] -> ShowS)
-> Show EventType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> EventType -> ShowS
showsPrec :: Int -> EventType -> ShowS
$cshow :: EventType -> String
show :: EventType -> String
$cshowList :: [EventType] -> ShowS
showList :: [EventType] -> ShowS
Show, EventType -> EventType -> Bool
(EventType -> EventType -> Bool)
-> (EventType -> EventType -> Bool) -> Eq EventType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: EventType -> EventType -> Bool
== :: EventType -> EventType -> Bool
$c/= :: EventType -> EventType -> Bool
/= :: EventType -> EventType -> Bool
Eq, ReadPrec [EventType]
ReadPrec EventType
Int -> ReadS EventType
ReadS [EventType]
(Int -> ReadS EventType)
-> ReadS [EventType]
-> ReadPrec EventType
-> ReadPrec [EventType]
-> Read EventType
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS EventType
readsPrec :: Int -> ReadS EventType
$creadList :: ReadS [EventType]
readList :: ReadS [EventType]
$creadPrec :: ReadPrec EventType
readPrec :: ReadPrec EventType
$creadListPrec :: ReadPrec [EventType]
readListPrec :: ReadPrec [EventType]
Read, (forall x. EventType -> Rep EventType x)
-> (forall x. Rep EventType x -> EventType) -> Generic EventType
forall x. Rep EventType x -> EventType
forall x. EventType -> Rep EventType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. EventType -> Rep EventType x
from :: forall x. EventType -> Rep EventType x
$cto :: forall x. Rep EventType x -> EventType
to :: forall x. Rep EventType x -> EventType
Generic)
instance ToJSON EventType where
  toJSON :: EventType -> Value
toJSON (EventTypeCustom Text
e) = Text -> Value
forall a. ToJSON a => a -> Value
toJSON Text
e
  toJSON EventType
e = EventType -> Value
forall a.
(Generic a, GToJSON Zero (Rep a), Typeable a) =>
a -> Value
genericToJSONWithModifier EventType
e
data Command
  = CommandCancel
  | CommandInitialize
  | CommandConfigurationDone
  | CommandLaunch
  | CommandAttach
  | CommandRestart
  | CommandDisconnect
  | CommandTerminate
  | CommandBreakpointLocations
  | CommandSetBreakpoints
  | CommandSetFunctionBreakpoints
  | CommandSetExceptionBreakpoints
  | CommandDataBreakpointInfo
  | CommandSetDataBreakpoints
  | CommandSetInstructionBreakpoints
  | CommandContinue
  | CommandNext
  | CommandStepIn
  | CommandStepOut
  | CommandStepBack
  | CommandReverseContinue
  | CommandRestartFrame
  | CommandGoTo
  | CommandPause
  | CommandStackTrace
  | CommandScopes
  | CommandVariables
  | CommandSetVariable
  | CommandSource
  | CommandThreads
  | CommandTerminateThreads
  | CommandModules
  | CommandLoadedSources
  | CommandEvaluate
  | CommandSetExpression
  | CommandStepInTargets
  | CommandGoToTargets
  | CommandCompletions
  | CommandExceptionInfo
  | CommandReadMemory
  | CommandWriteMemory
  | CommandDisassemble
  | CustomCommand Text
  deriving stock (Int -> Command -> ShowS
[Command] -> ShowS
Command -> String
(Int -> Command -> ShowS)
-> (Command -> String) -> ([Command] -> ShowS) -> Show Command
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Command -> ShowS
showsPrec :: Int -> Command -> ShowS
$cshow :: Command -> String
show :: Command -> String
$cshowList :: [Command] -> ShowS
showList :: [Command] -> ShowS
Show, Command -> Command -> Bool
(Command -> Command -> Bool)
-> (Command -> Command -> Bool) -> Eq Command
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Command -> Command -> Bool
== :: Command -> Command -> Bool
$c/= :: Command -> Command -> Bool
/= :: Command -> Command -> Bool
Eq, ReadPrec [Command]
ReadPrec Command
Int -> ReadS Command
ReadS [Command]
(Int -> ReadS Command)
-> ReadS [Command]
-> ReadPrec Command
-> ReadPrec [Command]
-> Read Command
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Command
readsPrec :: Int -> ReadS Command
$creadList :: ReadS [Command]
readList :: ReadS [Command]
$creadPrec :: ReadPrec Command
readPrec :: ReadPrec Command
$creadListPrec :: ReadPrec [Command]
readListPrec :: ReadPrec [Command]
Read, (forall x. Command -> Rep Command x)
-> (forall x. Rep Command x -> Command) -> Generic Command
forall x. Rep Command x -> Command
forall x. Command -> Rep Command x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Command -> Rep Command x
from :: forall x. Command -> Rep Command x
$cto :: forall x. Rep Command x -> Command
to :: forall x. Rep Command x -> Command
Generic)
instance FromJSON Command where
  parseJSON :: Value -> Parser Command
parseJSON = String -> (Text -> Parser Command) -> Value -> Parser Command
forall a. String -> (Text -> Parser a) -> Value -> Parser a
withText String
name ((Text -> Parser Command) -> Value -> Parser Command)
-> (Text -> Parser Command) -> Value -> Parser Command
forall a b. (a -> b) -> a -> b
$ \Text
command ->
    case String -> Maybe Command
forall a. Read a => String -> Maybe a
readMaybe (String
name String -> ShowS
forall a. Semigroup a => a -> a -> a
<> ShowS
capitalize (Text -> String
T.unpack Text
command)) of
      Just Command
cmd ->
        Command -> Parser Command
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Command
cmd
      Maybe Command
Nothing ->
        Command -> Parser Command
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Text -> Command
CustomCommand Text
command)
    where
      name :: String
name = TypeRep -> String
forall a. Show a => a -> String
show (Proxy Command -> TypeRep
forall {k} (proxy :: k -> *) (a :: k).
Typeable a =>
proxy a -> TypeRep
typeRep (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @Command))
instance ToJSON Command where
  toJSON :: Command -> Value
toJSON (CustomCommand Text
x) = Text -> Value
forall a. ToJSON a => a -> Value
toJSON Text
x
  toJSON Command
cmd = Command -> Value
forall a.
(Generic a, GToJSON Zero (Rep a), Typeable a) =>
a -> Value
genericToJSONWithModifier Command
cmd
data ReverseCommand
  = ReverseCommandRunInTerminal
  | ReverseCommandStartDebugging
  deriving stock (Int -> ReverseCommand -> ShowS
[ReverseCommand] -> ShowS
ReverseCommand -> String
(Int -> ReverseCommand -> ShowS)
-> (ReverseCommand -> String)
-> ([ReverseCommand] -> ShowS)
-> Show ReverseCommand
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ReverseCommand -> ShowS
showsPrec :: Int -> ReverseCommand -> ShowS
$cshow :: ReverseCommand -> String
show :: ReverseCommand -> String
$cshowList :: [ReverseCommand] -> ShowS
showList :: [ReverseCommand] -> ShowS
Show, ReverseCommand -> ReverseCommand -> Bool
(ReverseCommand -> ReverseCommand -> Bool)
-> (ReverseCommand -> ReverseCommand -> Bool) -> Eq ReverseCommand
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ReverseCommand -> ReverseCommand -> Bool
== :: ReverseCommand -> ReverseCommand -> Bool
$c/= :: ReverseCommand -> ReverseCommand -> Bool
/= :: ReverseCommand -> ReverseCommand -> Bool
Eq, ReadPrec [ReverseCommand]
ReadPrec ReverseCommand
Int -> ReadS ReverseCommand
ReadS [ReverseCommand]
(Int -> ReadS ReverseCommand)
-> ReadS [ReverseCommand]
-> ReadPrec ReverseCommand
-> ReadPrec [ReverseCommand]
-> Read ReverseCommand
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ReverseCommand
readsPrec :: Int -> ReadS ReverseCommand
$creadList :: ReadS [ReverseCommand]
readList :: ReadS [ReverseCommand]
$creadPrec :: ReadPrec ReverseCommand
readPrec :: ReadPrec ReverseCommand
$creadListPrec :: ReadPrec [ReverseCommand]
readListPrec :: ReadPrec [ReverseCommand]
Read, (forall x. ReverseCommand -> Rep ReverseCommand x)
-> (forall x. Rep ReverseCommand x -> ReverseCommand)
-> Generic ReverseCommand
forall x. Rep ReverseCommand x -> ReverseCommand
forall x. ReverseCommand -> Rep ReverseCommand x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ReverseCommand -> Rep ReverseCommand x
from :: forall x. ReverseCommand -> Rep ReverseCommand x
$cto :: forall x. Rep ReverseCommand x -> ReverseCommand
to :: forall x. Rep ReverseCommand x -> ReverseCommand
Generic)
instance FromJSON ReverseCommand where
  parseJSON :: Value -> Parser ReverseCommand
parseJSON = String
-> (Text -> Parser ReverseCommand)
-> Value
-> Parser ReverseCommand
forall a. String -> (Text -> Parser a) -> Value -> Parser a
withText String
name ((Text -> Parser ReverseCommand) -> Value -> Parser ReverseCommand)
-> (Text -> Parser ReverseCommand)
-> Value
-> Parser ReverseCommand
forall a b. (a -> b) -> a -> b
$ \Text
command ->
    case String -> Maybe ReverseCommand
forall a. Read a => String -> Maybe a
readMaybe (String
name String -> ShowS
forall a. Semigroup a => a -> a -> a
<> ShowS
capitalize (Text -> String
T.unpack Text
command)) of
      Just ReverseCommand
cmd ->
        ReverseCommand -> Parser ReverseCommand
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ReverseCommand
cmd
      Maybe ReverseCommand
Nothing ->
        String -> Parser ReverseCommand
forall a. String -> Parser a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Parser ReverseCommand)
-> String -> Parser ReverseCommand
forall a b. (a -> b) -> a -> b
$ String
"Unknown reverse command: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Text -> String
forall a. Show a => a -> String
show Text
command
    where
      name :: String
name = TypeRep -> String
forall a. Show a => a -> String
show (Proxy ReverseCommand -> TypeRep
forall {k} (proxy :: k -> *) (a :: k).
Typeable a =>
proxy a -> TypeRep
typeRep (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @ReverseCommand))
instance ToJSON ReverseCommand where
  toJSON :: ReverseCommand -> Value
toJSON ReverseCommand
cmd = ReverseCommand -> Value
forall a.
(Generic a, GToJSON Zero (Rep a), Typeable a) =>
a -> Value
genericToJSONWithModifier ReverseCommand
cmd
data ErrorMessage
  = ErrorMessageCancelled
  | ErrorMessageNotStopped
  | ErrorMessage Text
  deriving stock (Int -> ErrorMessage -> ShowS
[ErrorMessage] -> ShowS
ErrorMessage -> String
(Int -> ErrorMessage -> ShowS)
-> (ErrorMessage -> String)
-> ([ErrorMessage] -> ShowS)
-> Show ErrorMessage
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ErrorMessage -> ShowS
showsPrec :: Int -> ErrorMessage -> ShowS
$cshow :: ErrorMessage -> String
show :: ErrorMessage -> String
$cshowList :: [ErrorMessage] -> ShowS
showList :: [ErrorMessage] -> ShowS
Show, ErrorMessage -> ErrorMessage -> Bool
(ErrorMessage -> ErrorMessage -> Bool)
-> (ErrorMessage -> ErrorMessage -> Bool) -> Eq ErrorMessage
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ErrorMessage -> ErrorMessage -> Bool
== :: ErrorMessage -> ErrorMessage -> Bool
$c/= :: ErrorMessage -> ErrorMessage -> Bool
/= :: ErrorMessage -> ErrorMessage -> Bool
Eq, (forall x. ErrorMessage -> Rep ErrorMessage x)
-> (forall x. Rep ErrorMessage x -> ErrorMessage)
-> Generic ErrorMessage
forall x. Rep ErrorMessage x -> ErrorMessage
forall x. ErrorMessage -> Rep ErrorMessage x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ErrorMessage -> Rep ErrorMessage x
from :: forall x. ErrorMessage -> Rep ErrorMessage x
$cto :: forall x. Rep ErrorMessage x -> ErrorMessage
to :: forall x. Rep ErrorMessage x -> ErrorMessage
Generic)
instance IsString ErrorMessage where
  fromString :: String -> ErrorMessage
fromString = Text -> ErrorMessage
ErrorMessage (Text -> ErrorMessage)
-> (String -> Text) -> String -> ErrorMessage
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
T.pack
instance ToJSON ErrorMessage where
  toJSON :: ErrorMessage -> Value
toJSON (ErrorMessage Text
e) = Text -> Value
forall a. ToJSON a => a -> Value
toJSON Text
e
  toJSON ErrorMessage
msg = ErrorMessage -> Value
forall a.
(Generic a, GToJSON Zero (Rep a), Typeable a) =>
a -> Value
genericToJSONWithModifier ErrorMessage
msg
data BreakpointLocation
  = BreakpointLocation
  { BreakpointLocation -> Int
breakpointLocationLine :: Int
    
    
    
  , BreakpointLocation -> Maybe Int
breakpointLocationColumn :: Maybe Int
    
    
    
    
    
  , BreakpointLocation -> Maybe Int
breakpointLocationEndLine :: Maybe Int
    
    
    
  , BreakpointLocation -> Maybe Int
breakpointLocationEndColumn :: Maybe Int
    
    
    
    
    
  } deriving stock (BreakpointLocation -> BreakpointLocation -> Bool
(BreakpointLocation -> BreakpointLocation -> Bool)
-> (BreakpointLocation -> BreakpointLocation -> Bool)
-> Eq BreakpointLocation
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: BreakpointLocation -> BreakpointLocation -> Bool
== :: BreakpointLocation -> BreakpointLocation -> Bool
$c/= :: BreakpointLocation -> BreakpointLocation -> Bool
/= :: BreakpointLocation -> BreakpointLocation -> Bool
Eq, Int -> BreakpointLocation -> ShowS
[BreakpointLocation] -> ShowS
BreakpointLocation -> String
(Int -> BreakpointLocation -> ShowS)
-> (BreakpointLocation -> String)
-> ([BreakpointLocation] -> ShowS)
-> Show BreakpointLocation
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> BreakpointLocation -> ShowS
showsPrec :: Int -> BreakpointLocation -> ShowS
$cshow :: BreakpointLocation -> String
show :: BreakpointLocation -> String
$cshowList :: [BreakpointLocation] -> ShowS
showList :: [BreakpointLocation] -> ShowS
Show, (forall x. BreakpointLocation -> Rep BreakpointLocation x)
-> (forall x. Rep BreakpointLocation x -> BreakpointLocation)
-> Generic BreakpointLocation
forall x. Rep BreakpointLocation x -> BreakpointLocation
forall x. BreakpointLocation -> Rep BreakpointLocation x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. BreakpointLocation -> Rep BreakpointLocation x
from :: forall x. BreakpointLocation -> Rep BreakpointLocation x
$cto :: forall x. Rep BreakpointLocation x -> BreakpointLocation
to :: forall x. Rep BreakpointLocation x -> BreakpointLocation
Generic)
defaultBreakpointLocation :: BreakpointLocation
defaultBreakpointLocation :: BreakpointLocation
defaultBreakpointLocation
  = BreakpointLocation
  { breakpointLocationLine :: Int
breakpointLocationLine = Int
0
  , breakpointLocationColumn :: Maybe Int
breakpointLocationColumn = Maybe Int
forall a. Maybe a
Nothing
  , breakpointLocationEndLine :: Maybe Int
breakpointLocationEndLine = Maybe Int
forall a. Maybe a
Nothing
  , breakpointLocationEndColumn :: Maybe Int
breakpointLocationEndColumn = Maybe Int
forall a. Maybe a
Nothing
  }
instance ToJSON BreakpointLocation where
  toJSON :: BreakpointLocation -> Value
toJSON = BreakpointLocation -> Value
forall a.
(Generic a, GToJSON Zero (Rep a), Typeable a) =>
a -> Value
genericToJSONWithModifier
data ContinueResponse
  = ContinueResponse
  { ContinueResponse -> Bool
continueResponseAllThreadsContinued :: Bool
    
    
    
    
    
  } deriving stock (Int -> ContinueResponse -> ShowS
[ContinueResponse] -> ShowS
ContinueResponse -> String
(Int -> ContinueResponse -> ShowS)
-> (ContinueResponse -> String)
-> ([ContinueResponse] -> ShowS)
-> Show ContinueResponse
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ContinueResponse -> ShowS
showsPrec :: Int -> ContinueResponse -> ShowS
$cshow :: ContinueResponse -> String
show :: ContinueResponse -> String
$cshowList :: [ContinueResponse] -> ShowS
showList :: [ContinueResponse] -> ShowS
Show, ContinueResponse -> ContinueResponse -> Bool
(ContinueResponse -> ContinueResponse -> Bool)
-> (ContinueResponse -> ContinueResponse -> Bool)
-> Eq ContinueResponse
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ContinueResponse -> ContinueResponse -> Bool
== :: ContinueResponse -> ContinueResponse -> Bool
$c/= :: ContinueResponse -> ContinueResponse -> Bool
/= :: ContinueResponse -> ContinueResponse -> Bool
Eq, (forall x. ContinueResponse -> Rep ContinueResponse x)
-> (forall x. Rep ContinueResponse x -> ContinueResponse)
-> Generic ContinueResponse
forall x. Rep ContinueResponse x -> ContinueResponse
forall x. ContinueResponse -> Rep ContinueResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ContinueResponse -> Rep ContinueResponse x
from :: forall x. ContinueResponse -> Rep ContinueResponse x
$cto :: forall x. Rep ContinueResponse x -> ContinueResponse
to :: forall x. Rep ContinueResponse x -> ContinueResponse
Generic)
instance ToJSON ContinueResponse where
  toJSON :: ContinueResponse -> Value
toJSON = ContinueResponse -> Value
forall a.
(Generic a, GToJSON Zero (Rep a), Typeable a) =>
a -> Value
genericToJSONWithModifier
newtype ErrorResponse
  = ErrorResponse
  { ErrorResponse -> Maybe Message
errorResponseError :: Maybe Message
  } deriving stock (Int -> ErrorResponse -> ShowS
[ErrorResponse] -> ShowS
ErrorResponse -> String
(Int -> ErrorResponse -> ShowS)
-> (ErrorResponse -> String)
-> ([ErrorResponse] -> ShowS)
-> Show ErrorResponse
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ErrorResponse -> ShowS
showsPrec :: Int -> ErrorResponse -> ShowS
$cshow :: ErrorResponse -> String
show :: ErrorResponse -> String
$cshowList :: [ErrorResponse] -> ShowS
showList :: [ErrorResponse] -> ShowS
Show, ErrorResponse -> ErrorResponse -> Bool
(ErrorResponse -> ErrorResponse -> Bool)
-> (ErrorResponse -> ErrorResponse -> Bool) -> Eq ErrorResponse
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ErrorResponse -> ErrorResponse -> Bool
== :: ErrorResponse -> ErrorResponse -> Bool
$c/= :: ErrorResponse -> ErrorResponse -> Bool
/= :: ErrorResponse -> ErrorResponse -> Bool
Eq, (forall x. ErrorResponse -> Rep ErrorResponse x)
-> (forall x. Rep ErrorResponse x -> ErrorResponse)
-> Generic ErrorResponse
forall x. Rep ErrorResponse x -> ErrorResponse
forall x. ErrorResponse -> Rep ErrorResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ErrorResponse -> Rep ErrorResponse x
from :: forall x. ErrorResponse -> Rep ErrorResponse x
$cto :: forall x. Rep ErrorResponse x -> ErrorResponse
to :: forall x. Rep ErrorResponse x -> ErrorResponse
Generic)
instance ToJSON ErrorResponse where
  toJSON :: ErrorResponse -> Value
toJSON = ErrorResponse -> Value
forall a.
(Generic a, GToJSON Zero (Rep a), Typeable a) =>
a -> Value
genericToJSONWithModifier
data Message
  = Message
  { Message -> Int
messageId :: Int
    
    
    
    
    
    
    
  , Message -> Text
messageFormat :: Text
    
    
    
    
    
  , Message -> Maybe (HashMap Text Text)
messageVariables :: Maybe (H.HashMap Text Text)
    
    
    
    
  , Message -> Maybe Bool
messageSendTelemetry :: Maybe Bool
    
    
    
  , Message -> Maybe Bool
messageShowUser :: Maybe Bool
    
    
    
  , Message -> Maybe Text
messageUrl :: Maybe Text
    
    
    
  , Message -> Maybe Text
messageUrlLabel :: Maybe Text
    
    
    
  } deriving stock (Int -> Message -> ShowS
[Message] -> ShowS
Message -> String
(Int -> Message -> ShowS)
-> (Message -> String) -> ([Message] -> ShowS) -> Show Message
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Message -> ShowS
showsPrec :: Int -> Message -> ShowS
$cshow :: Message -> String
show :: Message -> String
$cshowList :: [Message] -> ShowS
showList :: [Message] -> ShowS
Show, Message -> Message -> Bool
(Message -> Message -> Bool)
-> (Message -> Message -> Bool) -> Eq Message
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Message -> Message -> Bool
== :: Message -> Message -> Bool
$c/= :: Message -> Message -> Bool
/= :: Message -> Message -> Bool
Eq, (forall x. Message -> Rep Message x)
-> (forall x. Rep Message x -> Message) -> Generic Message
forall x. Rep Message x -> Message
forall x. Message -> Rep Message x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Message -> Rep Message x
from :: forall x. Message -> Rep Message x
$cto :: forall x. Rep Message x -> Message
to :: forall x. Rep Message x -> Message
Generic)
defaultMessage :: Message
defaultMessage :: Message
defaultMessage
  = Message
  { messageId :: Int
messageId = Int
0
  , messageFormat :: Text
messageFormat = Text
forall a. Monoid a => a
mempty
  , messageVariables :: Maybe (HashMap Text Text)
messageVariables = Maybe (HashMap Text Text)
forall a. Maybe a
Nothing
  , messageSendTelemetry :: Maybe Bool
messageSendTelemetry = Maybe Bool
forall a. Maybe a
Nothing
  , messageShowUser :: Maybe Bool
messageShowUser = Maybe Bool
forall a. Maybe a
Nothing
  , messageUrl :: Maybe Text
messageUrl = Maybe Text
forall a. Maybe a
Nothing
  , messageUrlLabel :: Maybe Text
messageUrlLabel = Maybe Text
forall a. Maybe a
Nothing
  }
instance ToJSON Message where
  toJSON :: Message -> Value
toJSON = Message -> Value
forall a.
(Generic a, GToJSON Zero (Rep a), Typeable a) =>
a -> Value
genericToJSONWithModifier
data RunInTerminalResponse
  = RunInTerminalResponse
  { RunInTerminalResponse -> Maybe Int
runInTerminalResponseProcessId :: Maybe Int
    
    
    
    
  , RunInTerminalResponse -> Maybe Int
runInTerminalResponseShellProcessId :: Maybe Int
    
    
    
    
  } deriving stock (Int -> RunInTerminalResponse -> ShowS
[RunInTerminalResponse] -> ShowS
RunInTerminalResponse -> String
(Int -> RunInTerminalResponse -> ShowS)
-> (RunInTerminalResponse -> String)
-> ([RunInTerminalResponse] -> ShowS)
-> Show RunInTerminalResponse
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RunInTerminalResponse -> ShowS
showsPrec :: Int -> RunInTerminalResponse -> ShowS
$cshow :: RunInTerminalResponse -> String
show :: RunInTerminalResponse -> String
$cshowList :: [RunInTerminalResponse] -> ShowS
showList :: [RunInTerminalResponse] -> ShowS
Show, RunInTerminalResponse -> RunInTerminalResponse -> Bool
(RunInTerminalResponse -> RunInTerminalResponse -> Bool)
-> (RunInTerminalResponse -> RunInTerminalResponse -> Bool)
-> Eq RunInTerminalResponse
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RunInTerminalResponse -> RunInTerminalResponse -> Bool
== :: RunInTerminalResponse -> RunInTerminalResponse -> Bool
$c/= :: RunInTerminalResponse -> RunInTerminalResponse -> Bool
/= :: RunInTerminalResponse -> RunInTerminalResponse -> Bool
Eq, (forall x. RunInTerminalResponse -> Rep RunInTerminalResponse x)
-> (forall x. Rep RunInTerminalResponse x -> RunInTerminalResponse)
-> Generic RunInTerminalResponse
forall x. Rep RunInTerminalResponse x -> RunInTerminalResponse
forall x. RunInTerminalResponse -> Rep RunInTerminalResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. RunInTerminalResponse -> Rep RunInTerminalResponse x
from :: forall x. RunInTerminalResponse -> Rep RunInTerminalResponse x
$cto :: forall x. Rep RunInTerminalResponse x -> RunInTerminalResponse
to :: forall x. Rep RunInTerminalResponse x -> RunInTerminalResponse
Generic)
instance ToJSON RunInTerminalResponse where
  toJSON :: RunInTerminalResponse -> Value
toJSON = RunInTerminalResponse -> Value
forall a.
(Generic a, GToJSON Zero (Rep a), Typeable a) =>
a -> Value
genericToJSONWithModifier
instance FromJSON RunInTerminalResponse where
  parseJSON :: Value -> Parser RunInTerminalResponse
parseJSON = Value -> Parser RunInTerminalResponse
forall a.
(Generic a, GFromJSON Zero (Rep a), Typeable a) =>
Value -> Parser a
genericParseJSONWithModifier
data ModulesResponse
  = ModulesResponse
  { ModulesResponse -> [Module]
modulesResponseModules :: [Module]
    
    
    
  , ModulesResponse -> Maybe Int
modulesResponseTotalModules :: Maybe Int
    
    
    
  } deriving stock (Int -> ModulesResponse -> ShowS
[ModulesResponse] -> ShowS
ModulesResponse -> String
(Int -> ModulesResponse -> ShowS)
-> (ModulesResponse -> String)
-> ([ModulesResponse] -> ShowS)
-> Show ModulesResponse
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ModulesResponse -> ShowS
showsPrec :: Int -> ModulesResponse -> ShowS
$cshow :: ModulesResponse -> String
show :: ModulesResponse -> String
$cshowList :: [ModulesResponse] -> ShowS
showList :: [ModulesResponse] -> ShowS
Show, ModulesResponse -> ModulesResponse -> Bool
(ModulesResponse -> ModulesResponse -> Bool)
-> (ModulesResponse -> ModulesResponse -> Bool)
-> Eq ModulesResponse
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ModulesResponse -> ModulesResponse -> Bool
== :: ModulesResponse -> ModulesResponse -> Bool
$c/= :: ModulesResponse -> ModulesResponse -> Bool
/= :: ModulesResponse -> ModulesResponse -> Bool
Eq, (forall x. ModulesResponse -> Rep ModulesResponse x)
-> (forall x. Rep ModulesResponse x -> ModulesResponse)
-> Generic ModulesResponse
forall x. Rep ModulesResponse x -> ModulesResponse
forall x. ModulesResponse -> Rep ModulesResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ModulesResponse -> Rep ModulesResponse x
from :: forall x. ModulesResponse -> Rep ModulesResponse x
$cto :: forall x. Rep ModulesResponse x -> ModulesResponse
to :: forall x. Rep ModulesResponse x -> ModulesResponse
Generic)
instance ToJSON ModulesResponse where
  toJSON :: ModulesResponse -> Value
toJSON = ModulesResponse -> Value
forall a.
(Generic a, GToJSON Zero (Rep a), Typeable a) =>
a -> Value
genericToJSONWithModifier
data Module
  = Module
  { Module -> Either Text Int
moduleId :: Either Text Int
    
    
    
  , Module -> Text
moduleName :: Text
    
    
    
  , Module -> Maybe Text
modulePath :: Maybe Text
    
    
    
    
    
  , Module -> Maybe Bool
moduleIsOptimized :: Maybe Bool
    
    
    
  , Module -> Maybe Bool
moduleIsUserCode :: Maybe Bool
    
    
    
    
  , Module -> Maybe Text
moduleVersion :: Maybe Text
    
    
    
  , Module -> Maybe Text
moduleSymbolStatus :: Maybe Text
    
    
    
    
  , Module -> Maybe Text
moduleSymbolFilePath :: Maybe Text
    
    
    
    
  , Module -> Maybe Text
moduleDateTimeStamp :: Maybe Text
    
    
    
  , Module -> Maybe Text
moduleAddressRange :: Maybe Text
    
    
    
  } deriving stock (Int -> Module -> ShowS
[Module] -> ShowS
Module -> String
(Int -> Module -> ShowS)
-> (Module -> String) -> ([Module] -> ShowS) -> Show Module
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Module -> ShowS
showsPrec :: Int -> Module -> ShowS
$cshow :: Module -> String
show :: Module -> String
$cshowList :: [Module] -> ShowS
showList :: [Module] -> ShowS
Show, Module -> Module -> Bool
(Module -> Module -> Bool)
-> (Module -> Module -> Bool) -> Eq Module
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Module -> Module -> Bool
== :: Module -> Module -> Bool
$c/= :: Module -> Module -> Bool
/= :: Module -> Module -> Bool
Eq, (forall x. Module -> Rep Module x)
-> (forall x. Rep Module x -> Module) -> Generic Module
forall x. Rep Module x -> Module
forall x. Module -> Rep Module x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Module -> Rep Module x
from :: forall x. Module -> Rep Module x
$cto :: forall x. Rep Module x -> Module
to :: forall x. Rep Module x -> Module
Generic)
instance ToJSON Module where
  toJSON :: Module -> Value
toJSON = Module -> Value
forall a.
(Generic a, GToJSON Zero (Rep a), Typeable a) =>
a -> Value
genericToJSONWithModifier
defaultModule :: Module
defaultModule :: Module
defaultModule
  = Module
  { moduleId :: Either Text Int
moduleId = Int -> Either Text Int
forall a b. b -> Either a b
Right Int
0
  , moduleName :: Text
moduleName = Text
forall a. Monoid a => a
mempty
  , modulePath :: Maybe Text
modulePath = Maybe Text
forall a. Monoid a => a
mempty
  , moduleIsOptimized :: Maybe Bool
moduleIsOptimized = Maybe Bool
forall a. Maybe a
Nothing
  , moduleIsUserCode :: Maybe Bool
moduleIsUserCode = Maybe Bool
forall a. Maybe a
Nothing
  , moduleVersion :: Maybe Text
moduleVersion = Maybe Text
forall a. Maybe a
Nothing
  , moduleSymbolStatus :: Maybe Text
moduleSymbolStatus = Maybe Text
forall a. Maybe a
Nothing
  , moduleSymbolFilePath :: Maybe Text
moduleSymbolFilePath = Maybe Text
forall a. Maybe a
Nothing
  , moduleDateTimeStamp :: Maybe Text
moduleDateTimeStamp = Maybe Text
forall a. Maybe a
Nothing
  , moduleAddressRange :: Maybe Text
moduleAddressRange = Maybe Text
forall a. Maybe a
Nothing
  }
data DataBreakpointInfoResponse
  = DataBreakpointInfoResponse
  { DataBreakpointInfoResponse -> Maybe Text
dataBreakpointInfoResponseDataId :: Maybe Text
    
    
    
    
    
  , DataBreakpointInfoResponse -> Text
dataBreakpointInfoResponseDescription :: Text
    
    
    
    
  , DataBreakpointInfoResponse -> [DataBreakpointAccessType]
dataBreakpointInfoResponseDescriptionAccessTypes :: [DataBreakpointAccessType]
    
    
    
    
  , DataBreakpointInfoResponse -> Maybe Bool
dataBreakpointInfoResponseDescriptionCanPersist :: Maybe Bool
    
    
    
    
  } deriving stock (Int -> DataBreakpointInfoResponse -> ShowS
[DataBreakpointInfoResponse] -> ShowS
DataBreakpointInfoResponse -> String
(Int -> DataBreakpointInfoResponse -> ShowS)
-> (DataBreakpointInfoResponse -> String)
-> ([DataBreakpointInfoResponse] -> ShowS)
-> Show DataBreakpointInfoResponse
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> DataBreakpointInfoResponse -> ShowS
showsPrec :: Int -> DataBreakpointInfoResponse -> ShowS
$cshow :: DataBreakpointInfoResponse -> String
show :: DataBreakpointInfoResponse -> String
$cshowList :: [DataBreakpointInfoResponse] -> ShowS
showList :: [DataBreakpointInfoResponse] -> ShowS
Show, DataBreakpointInfoResponse -> DataBreakpointInfoResponse -> Bool
(DataBreakpointInfoResponse -> DataBreakpointInfoResponse -> Bool)
-> (DataBreakpointInfoResponse
    -> DataBreakpointInfoResponse -> Bool)
-> Eq DataBreakpointInfoResponse
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DataBreakpointInfoResponse -> DataBreakpointInfoResponse -> Bool
== :: DataBreakpointInfoResponse -> DataBreakpointInfoResponse -> Bool
$c/= :: DataBreakpointInfoResponse -> DataBreakpointInfoResponse -> Bool
/= :: DataBreakpointInfoResponse -> DataBreakpointInfoResponse -> Bool
Eq, (forall x.
 DataBreakpointInfoResponse -> Rep DataBreakpointInfoResponse x)
-> (forall x.
    Rep DataBreakpointInfoResponse x -> DataBreakpointInfoResponse)
-> Generic DataBreakpointInfoResponse
forall x.
Rep DataBreakpointInfoResponse x -> DataBreakpointInfoResponse
forall x.
DataBreakpointInfoResponse -> Rep DataBreakpointInfoResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x.
DataBreakpointInfoResponse -> Rep DataBreakpointInfoResponse x
from :: forall x.
DataBreakpointInfoResponse -> Rep DataBreakpointInfoResponse x
$cto :: forall x.
Rep DataBreakpointInfoResponse x -> DataBreakpointInfoResponse
to :: forall x.
Rep DataBreakpointInfoResponse x -> DataBreakpointInfoResponse
Generic)
instance ToJSON DataBreakpointInfoResponse where
  toJSON :: DataBreakpointInfoResponse -> Value
toJSON = DataBreakpointInfoResponse -> Value
forall a.
(Generic a, GToJSON Zero (Rep a), Typeable a) =>
a -> Value
genericToJSONWithModifier
data DataBreakpointAccessType
  = DataBreakpointAccessTypeRead
  | DataBreakpointAccessTypeWrite
  | DataBreakpointAccessTypeReadWrite
  deriving stock (Int -> DataBreakpointAccessType -> ShowS
[DataBreakpointAccessType] -> ShowS
DataBreakpointAccessType -> String
(Int -> DataBreakpointAccessType -> ShowS)
-> (DataBreakpointAccessType -> String)
-> ([DataBreakpointAccessType] -> ShowS)
-> Show DataBreakpointAccessType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> DataBreakpointAccessType -> ShowS
showsPrec :: Int -> DataBreakpointAccessType -> ShowS
$cshow :: DataBreakpointAccessType -> String
show :: DataBreakpointAccessType -> String
$cshowList :: [DataBreakpointAccessType] -> ShowS
showList :: [DataBreakpointAccessType] -> ShowS
Show, DataBreakpointAccessType -> DataBreakpointAccessType -> Bool
(DataBreakpointAccessType -> DataBreakpointAccessType -> Bool)
-> (DataBreakpointAccessType -> DataBreakpointAccessType -> Bool)
-> Eq DataBreakpointAccessType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DataBreakpointAccessType -> DataBreakpointAccessType -> Bool
== :: DataBreakpointAccessType -> DataBreakpointAccessType -> Bool
$c/= :: DataBreakpointAccessType -> DataBreakpointAccessType -> Bool
/= :: DataBreakpointAccessType -> DataBreakpointAccessType -> Bool
Eq, (forall x.
 DataBreakpointAccessType -> Rep DataBreakpointAccessType x)
-> (forall x.
    Rep DataBreakpointAccessType x -> DataBreakpointAccessType)
-> Generic DataBreakpointAccessType
forall x.
Rep DataBreakpointAccessType x -> DataBreakpointAccessType
forall x.
DataBreakpointAccessType -> Rep DataBreakpointAccessType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x.
DataBreakpointAccessType -> Rep DataBreakpointAccessType x
from :: forall x.
DataBreakpointAccessType -> Rep DataBreakpointAccessType x
$cto :: forall x.
Rep DataBreakpointAccessType x -> DataBreakpointAccessType
to :: forall x.
Rep DataBreakpointAccessType x -> DataBreakpointAccessType
Generic)
instance FromJSON DataBreakpointAccessType where
  parseJSON :: Value -> Parser DataBreakpointAccessType
parseJSON = Value -> Parser DataBreakpointAccessType
forall a.
(Generic a, GFromJSON Zero (Rep a), Typeable a) =>
Value -> Parser a
genericParseJSONWithModifier
instance ToJSON DataBreakpointAccessType where
  toJSON :: DataBreakpointAccessType -> Value
toJSON = DataBreakpointAccessType -> Value
forall a.
(Generic a, GToJSON Zero (Rep a), Typeable a) =>
a -> Value
genericToJSONWithModifier
data StackTraceResponse
  = StackTraceResponse
  { StackTraceResponse -> [StackFrame]
stackFrames :: [StackFrame]
    
    
    
    
    
  , StackTraceResponse -> Maybe Int
totalFrames :: Maybe Int
    
    
    
    
    
    
    
    
  } deriving stock (Int -> StackTraceResponse -> ShowS
[StackTraceResponse] -> ShowS
StackTraceResponse -> String
(Int -> StackTraceResponse -> ShowS)
-> (StackTraceResponse -> String)
-> ([StackTraceResponse] -> ShowS)
-> Show StackTraceResponse
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> StackTraceResponse -> ShowS
showsPrec :: Int -> StackTraceResponse -> ShowS
$cshow :: StackTraceResponse -> String
show :: StackTraceResponse -> String
$cshowList :: [StackTraceResponse] -> ShowS
showList :: [StackTraceResponse] -> ShowS
Show, StackTraceResponse -> StackTraceResponse -> Bool
(StackTraceResponse -> StackTraceResponse -> Bool)
-> (StackTraceResponse -> StackTraceResponse -> Bool)
-> Eq StackTraceResponse
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: StackTraceResponse -> StackTraceResponse -> Bool
== :: StackTraceResponse -> StackTraceResponse -> Bool
$c/= :: StackTraceResponse -> StackTraceResponse -> Bool
/= :: StackTraceResponse -> StackTraceResponse -> Bool
Eq)
instance ToJSON StackTraceResponse where
  toJSON :: StackTraceResponse -> Value
toJSON StackTraceResponse {[StackFrame]
Maybe Int
totalFrames :: StackTraceResponse -> Maybe Int
stackFrames :: StackTraceResponse -> [StackFrame]
stackFrames :: [StackFrame]
totalFrames :: Maybe Int
..}
    = [Pair] -> Value
object
    [ Key
"stackFrames" Key -> [StackFrame] -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= [StackFrame]
stackFrames
    , Key
"totalFrames" Key -> Maybe Int -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Maybe Int
totalFrames
    ]
newtype ScopesResponse
  = ScopesResponse
  { ScopesResponse -> [Scope]
scopes :: [Scope]
    
    
    
  } deriving stock (Int -> ScopesResponse -> ShowS
[ScopesResponse] -> ShowS
ScopesResponse -> String
(Int -> ScopesResponse -> ShowS)
-> (ScopesResponse -> String)
-> ([ScopesResponse] -> ShowS)
-> Show ScopesResponse
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ScopesResponse -> ShowS
showsPrec :: Int -> ScopesResponse -> ShowS
$cshow :: ScopesResponse -> String
show :: ScopesResponse -> String
$cshowList :: [ScopesResponse] -> ShowS
showList :: [ScopesResponse] -> ShowS
Show, ScopesResponse -> ScopesResponse -> Bool
(ScopesResponse -> ScopesResponse -> Bool)
-> (ScopesResponse -> ScopesResponse -> Bool) -> Eq ScopesResponse
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ScopesResponse -> ScopesResponse -> Bool
== :: ScopesResponse -> ScopesResponse -> Bool
$c/= :: ScopesResponse -> ScopesResponse -> Bool
/= :: ScopesResponse -> ScopesResponse -> Bool
Eq)
instance ToJSON ScopesResponse where
  toJSON :: ScopesResponse -> Value
toJSON ScopesResponse {[Scope]
scopes :: ScopesResponse -> [Scope]
scopes :: [Scope]
..}
    = [Pair] -> Value
object
    [ Key
"scopes" Key -> [Scope] -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= [Scope]
scopes
    ]
data Scope
  = Scope
  { Scope -> Text
scopeName :: Text
    
    
    
    
  , Scope -> Maybe ScopePresentationHint
scopePresentationHint :: Maybe ScopePresentationHint
    
    
    
    
    
    
    
    
    
    
  , Scope -> Int
scopeVariablesReference :: Int
    
    
    
    
    
    
  , Scope -> Maybe Int
scopeNamedVariables :: Maybe Int
    
    
    
    
    
  , Scope -> Maybe Int
scopeIndexedVariables :: Maybe Int
    
    
    
    
    
  , Scope -> Bool
scopeExpensive :: Bool
    
    
    
    
  , Scope -> Maybe Source
scopeSource :: Maybe Source
    
    
    
  , Scope -> Maybe Int
scopeLine :: Maybe Int
    
    
    
  , Scope -> Maybe Int
scopeColumn :: Maybe Int
    
    
    
    
    
  , Scope -> Maybe Int
scopeEndLine :: Maybe Int
    
    
    
  , Scope -> Maybe Int
scopeEndColumn :: Maybe Int
    
    
    
    
    
  } deriving stock (Int -> Scope -> ShowS
[Scope] -> ShowS
Scope -> String
(Int -> Scope -> ShowS)
-> (Scope -> String) -> ([Scope] -> ShowS) -> Show Scope
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Scope -> ShowS
showsPrec :: Int -> Scope -> ShowS
$cshow :: Scope -> String
show :: Scope -> String
$cshowList :: [Scope] -> ShowS
showList :: [Scope] -> ShowS
Show, Scope -> Scope -> Bool
(Scope -> Scope -> Bool) -> (Scope -> Scope -> Bool) -> Eq Scope
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Scope -> Scope -> Bool
== :: Scope -> Scope -> Bool
$c/= :: Scope -> Scope -> Bool
/= :: Scope -> Scope -> Bool
Eq, (forall x. Scope -> Rep Scope x)
-> (forall x. Rep Scope x -> Scope) -> Generic Scope
forall x. Rep Scope x -> Scope
forall x. Scope -> Rep Scope x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Scope -> Rep Scope x
from :: forall x. Scope -> Rep Scope x
$cto :: forall x. Rep Scope x -> Scope
to :: forall x. Rep Scope x -> Scope
Generic)
defaultScope :: Scope
defaultScope :: Scope
defaultScope
  = Scope
  { scopeName :: Text
scopeName = Text
forall a. Monoid a => a
mempty
  , scopePresentationHint :: Maybe ScopePresentationHint
scopePresentationHint = Maybe ScopePresentationHint
forall a. Maybe a
Nothing
  , scopeVariablesReference :: Int
scopeVariablesReference = Int
0
  , scopeNamedVariables :: Maybe Int
scopeNamedVariables = Maybe Int
forall a. Maybe a
Nothing
  , scopeIndexedVariables :: Maybe Int
scopeIndexedVariables = Maybe Int
forall a. Maybe a
Nothing
  , scopeExpensive :: Bool
scopeExpensive = Bool
False
  , scopeSource :: Maybe Source
scopeSource = Maybe Source
forall a. Maybe a
Nothing
  , scopeLine :: Maybe Int
scopeLine = Maybe Int
forall a. Maybe a
Nothing
  , scopeColumn :: Maybe Int
scopeColumn = Maybe Int
forall a. Maybe a
Nothing
  , scopeEndLine :: Maybe Int
scopeEndLine = Maybe Int
forall a. Maybe a
Nothing
  , scopeEndColumn :: Maybe Int
scopeEndColumn = Maybe Int
forall a. Maybe a
Nothing
  }
instance ToJSON Scope where
  toJSON :: Scope -> Value
toJSON = Scope -> Value
forall a.
(Generic a, GToJSON Zero (Rep a), Typeable a) =>
a -> Value
genericToJSONWithModifier
data ScopePresentationHint
  = ScopePresentationHintArguments
  | ScopePresentationHintLocals
  | ScopePresentationHintRegisters
  | ScopePresentationHint Text
  deriving stock (Int -> ScopePresentationHint -> ShowS
[ScopePresentationHint] -> ShowS
ScopePresentationHint -> String
(Int -> ScopePresentationHint -> ShowS)
-> (ScopePresentationHint -> String)
-> ([ScopePresentationHint] -> ShowS)
-> Show ScopePresentationHint
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ScopePresentationHint -> ShowS
showsPrec :: Int -> ScopePresentationHint -> ShowS
$cshow :: ScopePresentationHint -> String
show :: ScopePresentationHint -> String
$cshowList :: [ScopePresentationHint] -> ShowS
showList :: [ScopePresentationHint] -> ShowS
Show, ScopePresentationHint -> ScopePresentationHint -> Bool
(ScopePresentationHint -> ScopePresentationHint -> Bool)
-> (ScopePresentationHint -> ScopePresentationHint -> Bool)
-> Eq ScopePresentationHint
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ScopePresentationHint -> ScopePresentationHint -> Bool
== :: ScopePresentationHint -> ScopePresentationHint -> Bool
$c/= :: ScopePresentationHint -> ScopePresentationHint -> Bool
/= :: ScopePresentationHint -> ScopePresentationHint -> Bool
Eq, (forall x. ScopePresentationHint -> Rep ScopePresentationHint x)
-> (forall x. Rep ScopePresentationHint x -> ScopePresentationHint)
-> Generic ScopePresentationHint
forall x. Rep ScopePresentationHint x -> ScopePresentationHint
forall x. ScopePresentationHint -> Rep ScopePresentationHint x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ScopePresentationHint -> Rep ScopePresentationHint x
from :: forall x. ScopePresentationHint -> Rep ScopePresentationHint x
$cto :: forall x. Rep ScopePresentationHint x -> ScopePresentationHint
to :: forall x. Rep ScopePresentationHint x -> ScopePresentationHint
Generic)
instance ToJSON ScopePresentationHint where
  toJSON :: ScopePresentationHint -> Value
toJSON (ScopePresentationHint Text
hint) = Text -> Value
forall a. ToJSON a => a -> Value
toJSON Text
hint
  toJSON ScopePresentationHint
hint = ScopePresentationHint -> Value
forall a.
(Generic a, GToJSON Zero (Rep a), Typeable a) =>
a -> Value
genericToJSONWithModifier ScopePresentationHint
hint
data VariablesResponse
  = VariablesResponse
  { VariablesResponse -> [Variable]
variables :: [Variable]
    
    
    
  } deriving stock (Int -> VariablesResponse -> ShowS
[VariablesResponse] -> ShowS
VariablesResponse -> String
(Int -> VariablesResponse -> ShowS)
-> (VariablesResponse -> String)
-> ([VariablesResponse] -> ShowS)
-> Show VariablesResponse
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> VariablesResponse -> ShowS
showsPrec :: Int -> VariablesResponse -> ShowS
$cshow :: VariablesResponse -> String
show :: VariablesResponse -> String
$cshowList :: [VariablesResponse] -> ShowS
showList :: [VariablesResponse] -> ShowS
Show, VariablesResponse -> VariablesResponse -> Bool
(VariablesResponse -> VariablesResponse -> Bool)
-> (VariablesResponse -> VariablesResponse -> Bool)
-> Eq VariablesResponse
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: VariablesResponse -> VariablesResponse -> Bool
== :: VariablesResponse -> VariablesResponse -> Bool
$c/= :: VariablesResponse -> VariablesResponse -> Bool
/= :: VariablesResponse -> VariablesResponse -> Bool
Eq, (forall x. VariablesResponse -> Rep VariablesResponse x)
-> (forall x. Rep VariablesResponse x -> VariablesResponse)
-> Generic VariablesResponse
forall x. Rep VariablesResponse x -> VariablesResponse
forall x. VariablesResponse -> Rep VariablesResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. VariablesResponse -> Rep VariablesResponse x
from :: forall x. VariablesResponse -> Rep VariablesResponse x
$cto :: forall x. Rep VariablesResponse x -> VariablesResponse
to :: forall x. Rep VariablesResponse x -> VariablesResponse
Generic)
    deriving anyclass [VariablesResponse] -> Value
[VariablesResponse] -> Encoding
VariablesResponse -> Bool
VariablesResponse -> Value
VariablesResponse -> Encoding
(VariablesResponse -> Value)
-> (VariablesResponse -> Encoding)
-> ([VariablesResponse] -> Value)
-> ([VariablesResponse] -> Encoding)
-> (VariablesResponse -> Bool)
-> ToJSON VariablesResponse
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: VariablesResponse -> Value
toJSON :: VariablesResponse -> Value
$ctoEncoding :: VariablesResponse -> Encoding
toEncoding :: VariablesResponse -> Encoding
$ctoJSONList :: [VariablesResponse] -> Value
toJSONList :: [VariablesResponse] -> Value
$ctoEncodingList :: [VariablesResponse] -> Encoding
toEncodingList :: [VariablesResponse] -> Encoding
$comitField :: VariablesResponse -> Bool
omitField :: VariablesResponse -> Bool
ToJSON
data Variable
  = Variable
  { Variable -> Text
variableName :: Text
    
    
    
  , Variable -> Text
variableValue :: Text
    
    
    
    
    
    
    
    
    
  , Variable -> Maybe Text
variableType :: Maybe Text
    
    
    
    
    
    
  , Variable -> Maybe VariablePresentationHint
variablePresentationHint :: Maybe VariablePresentationHint
    
    
    
    
  , Variable -> Maybe Text
variableEvaluateName :: Maybe Text
    
    
    
    
  , Variable -> Int
variableVariablesReference :: Int
    
    
    
    
    
    
  , Variable -> Maybe Int
variableNamedVariables :: Maybe Int
    
    
    
    
    
  , Variable -> Maybe Int
variableIndexedVariables :: Maybe Int
    
    
    
    
    
  , Variable -> Maybe Text
variableMemoryReference :: Maybe Text
    
    
    
    
    
    
   } deriving stock (Int -> Variable -> ShowS
[Variable] -> ShowS
Variable -> String
(Int -> Variable -> ShowS)
-> (Variable -> String) -> ([Variable] -> ShowS) -> Show Variable
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Variable -> ShowS
showsPrec :: Int -> Variable -> ShowS
$cshow :: Variable -> String
show :: Variable -> String
$cshowList :: [Variable] -> ShowS
showList :: [Variable] -> ShowS
Show, Variable -> Variable -> Bool
(Variable -> Variable -> Bool)
-> (Variable -> Variable -> Bool) -> Eq Variable
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Variable -> Variable -> Bool
== :: Variable -> Variable -> Bool
$c/= :: Variable -> Variable -> Bool
/= :: Variable -> Variable -> Bool
Eq, (forall x. Variable -> Rep Variable x)
-> (forall x. Rep Variable x -> Variable) -> Generic Variable
forall x. Rep Variable x -> Variable
forall x. Variable -> Rep Variable x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Variable -> Rep Variable x
from :: forall x. Variable -> Rep Variable x
$cto :: forall x. Rep Variable x -> Variable
to :: forall x. Rep Variable x -> Variable
Generic)
defaultVariable :: Variable
defaultVariable :: Variable
defaultVariable
  = Variable
  { variableName :: Text
variableName = Text
forall a. Monoid a => a
mempty
  , variableValue :: Text
variableValue = Text
forall a. Monoid a => a
mempty
  , variableType :: Maybe Text
variableType = Maybe Text
forall a. Maybe a
Nothing
  , variablePresentationHint :: Maybe VariablePresentationHint
variablePresentationHint = Maybe VariablePresentationHint
forall a. Maybe a
Nothing
  , variableEvaluateName :: Maybe Text
variableEvaluateName = Maybe Text
forall a. Maybe a
Nothing
  , variableVariablesReference :: Int
variableVariablesReference = Int
0
  , variableNamedVariables :: Maybe Int
variableNamedVariables = Maybe Int
forall a. Maybe a
Nothing
  , variableIndexedVariables :: Maybe Int
variableIndexedVariables = Maybe Int
forall a. Maybe a
Nothing
  , variableMemoryReference :: Maybe Text
variableMemoryReference = Maybe Text
forall a. Maybe a
Nothing
  }
instance ToJSON Variable where
  toJSON :: Variable -> Value
toJSON = Variable -> Value
forall a.
(Generic a, GToJSON Zero (Rep a), Typeable a) =>
a -> Value
genericToJSONWithModifier
data VariablePresentationHint
  = VariablePresentationHint
  { VariablePresentationHint -> Maybe PresentationHintKind
variablePresentationHintKind :: Maybe PresentationHintKind
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
  , VariablePresentationHint -> Maybe [PresentationHintAttributes]
variablePresentationHintAttributes :: Maybe [PresentationHintAttributes]
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
  , VariablePresentationHint -> Maybe PresentationHintVisibility
variablePresentationHintVisibility :: Maybe PresentationHintVisibility
    
    
    
    
    
  , VariablePresentationHint -> Maybe Bool
variablePresentationHintLazy :: Maybe Bool
    
    
    
    
    
    
    
    
    
    
    
  } deriving stock (Int -> VariablePresentationHint -> ShowS
[VariablePresentationHint] -> ShowS
VariablePresentationHint -> String
(Int -> VariablePresentationHint -> ShowS)
-> (VariablePresentationHint -> String)
-> ([VariablePresentationHint] -> ShowS)
-> Show VariablePresentationHint
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> VariablePresentationHint -> ShowS
showsPrec :: Int -> VariablePresentationHint -> ShowS
$cshow :: VariablePresentationHint -> String
show :: VariablePresentationHint -> String
$cshowList :: [VariablePresentationHint] -> ShowS
showList :: [VariablePresentationHint] -> ShowS
Show, VariablePresentationHint -> VariablePresentationHint -> Bool
(VariablePresentationHint -> VariablePresentationHint -> Bool)
-> (VariablePresentationHint -> VariablePresentationHint -> Bool)
-> Eq VariablePresentationHint
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: VariablePresentationHint -> VariablePresentationHint -> Bool
== :: VariablePresentationHint -> VariablePresentationHint -> Bool
$c/= :: VariablePresentationHint -> VariablePresentationHint -> Bool
/= :: VariablePresentationHint -> VariablePresentationHint -> Bool
Eq, (forall x.
 VariablePresentationHint -> Rep VariablePresentationHint x)
-> (forall x.
    Rep VariablePresentationHint x -> VariablePresentationHint)
-> Generic VariablePresentationHint
forall x.
Rep VariablePresentationHint x -> VariablePresentationHint
forall x.
VariablePresentationHint -> Rep VariablePresentationHint x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x.
VariablePresentationHint -> Rep VariablePresentationHint x
from :: forall x.
VariablePresentationHint -> Rep VariablePresentationHint x
$cto :: forall x.
Rep VariablePresentationHint x -> VariablePresentationHint
to :: forall x.
Rep VariablePresentationHint x -> VariablePresentationHint
Generic)
defaultVariablePresentationHint :: VariablePresentationHint
defaultVariablePresentationHint :: VariablePresentationHint
defaultVariablePresentationHint
  = VariablePresentationHint
  { variablePresentationHintKind :: Maybe PresentationHintKind
variablePresentationHintKind = Maybe PresentationHintKind
forall a. Maybe a
Nothing
  , variablePresentationHintAttributes :: Maybe [PresentationHintAttributes]
variablePresentationHintAttributes = Maybe [PresentationHintAttributes]
forall a. Maybe a
Nothing
  , variablePresentationHintVisibility :: Maybe PresentationHintVisibility
variablePresentationHintVisibility = Maybe PresentationHintVisibility
forall a. Maybe a
Nothing
  , variablePresentationHintLazy :: Maybe Bool
variablePresentationHintLazy = Maybe Bool
forall a. Maybe a
Nothing
  }
instance ToJSON VariablePresentationHint where
  toJSON :: VariablePresentationHint -> Value
toJSON = VariablePresentationHint -> Value
forall a.
(Generic a, GToJSON Zero (Rep a), Typeable a) =>
a -> Value
genericToJSONWithModifier
data PresentationHintVisibility
  = PresentationHintVisibilityPublic
  | PresentationHintVisibilityPrivate
  | PresentationHintVisibilityProtected
  | PresentationHintVisibilityInternal
  | PresentationHintVisibilityFinal
  | PresentationHintVisibility String
  deriving stock (Int -> PresentationHintVisibility -> ShowS
[PresentationHintVisibility] -> ShowS
PresentationHintVisibility -> String
(Int -> PresentationHintVisibility -> ShowS)
-> (PresentationHintVisibility -> String)
-> ([PresentationHintVisibility] -> ShowS)
-> Show PresentationHintVisibility
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> PresentationHintVisibility -> ShowS
showsPrec :: Int -> PresentationHintVisibility -> ShowS
$cshow :: PresentationHintVisibility -> String
show :: PresentationHintVisibility -> String
$cshowList :: [PresentationHintVisibility] -> ShowS
showList :: [PresentationHintVisibility] -> ShowS
Show, PresentationHintVisibility -> PresentationHintVisibility -> Bool
(PresentationHintVisibility -> PresentationHintVisibility -> Bool)
-> (PresentationHintVisibility
    -> PresentationHintVisibility -> Bool)
-> Eq PresentationHintVisibility
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: PresentationHintVisibility -> PresentationHintVisibility -> Bool
== :: PresentationHintVisibility -> PresentationHintVisibility -> Bool
$c/= :: PresentationHintVisibility -> PresentationHintVisibility -> Bool
/= :: PresentationHintVisibility -> PresentationHintVisibility -> Bool
Eq, (forall x.
 PresentationHintVisibility -> Rep PresentationHintVisibility x)
-> (forall x.
    Rep PresentationHintVisibility x -> PresentationHintVisibility)
-> Generic PresentationHintVisibility
forall x.
Rep PresentationHintVisibility x -> PresentationHintVisibility
forall x.
PresentationHintVisibility -> Rep PresentationHintVisibility x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x.
PresentationHintVisibility -> Rep PresentationHintVisibility x
from :: forall x.
PresentationHintVisibility -> Rep PresentationHintVisibility x
$cto :: forall x.
Rep PresentationHintVisibility x -> PresentationHintVisibility
to :: forall x.
Rep PresentationHintVisibility x -> PresentationHintVisibility
Generic)
instance ToJSON PresentationHintVisibility where
  toJSON :: PresentationHintVisibility -> Value
toJSON (PresentationHintVisibility String
hint) = String -> Value
forall a. ToJSON a => a -> Value
toJSON String
hint
  toJSON PresentationHintVisibility
hint = PresentationHintVisibility -> Value
forall a.
(Generic a, GToJSON Zero (Rep a), Typeable a) =>
a -> Value
genericToJSONWithModifier PresentationHintVisibility
hint
data PresentationHintAttributes
  = PresentationHintAttributesStatic
  | PresentationHintAttributesConstant
  | PresentationHintAttributesReadOnly
  | PresentationHintAttributesRawText
  | PresentationHintAttributesHasObjectId
  | PresentationHintAttributesCanHaveObjectId
  | PresentationHintAttributesHasSideEffects
  | PresentationHintAttributesHasDataBreakpoint
  | PresentationHintAttributes String
  deriving stock (Int -> PresentationHintAttributes -> ShowS
[PresentationHintAttributes] -> ShowS
PresentationHintAttributes -> String
(Int -> PresentationHintAttributes -> ShowS)
-> (PresentationHintAttributes -> String)
-> ([PresentationHintAttributes] -> ShowS)
-> Show PresentationHintAttributes
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> PresentationHintAttributes -> ShowS
showsPrec :: Int -> PresentationHintAttributes -> ShowS
$cshow :: PresentationHintAttributes -> String
show :: PresentationHintAttributes -> String
$cshowList :: [PresentationHintAttributes] -> ShowS
showList :: [PresentationHintAttributes] -> ShowS
Show, PresentationHintAttributes -> PresentationHintAttributes -> Bool
(PresentationHintAttributes -> PresentationHintAttributes -> Bool)
-> (PresentationHintAttributes
    -> PresentationHintAttributes -> Bool)
-> Eq PresentationHintAttributes
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: PresentationHintAttributes -> PresentationHintAttributes -> Bool
== :: PresentationHintAttributes -> PresentationHintAttributes -> Bool
$c/= :: PresentationHintAttributes -> PresentationHintAttributes -> Bool
/= :: PresentationHintAttributes -> PresentationHintAttributes -> Bool
Eq, (forall x.
 PresentationHintAttributes -> Rep PresentationHintAttributes x)
-> (forall x.
    Rep PresentationHintAttributes x -> PresentationHintAttributes)
-> Generic PresentationHintAttributes
forall x.
Rep PresentationHintAttributes x -> PresentationHintAttributes
forall x.
PresentationHintAttributes -> Rep PresentationHintAttributes x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x.
PresentationHintAttributes -> Rep PresentationHintAttributes x
from :: forall x.
PresentationHintAttributes -> Rep PresentationHintAttributes x
$cto :: forall x.
Rep PresentationHintAttributes x -> PresentationHintAttributes
to :: forall x.
Rep PresentationHintAttributes x -> PresentationHintAttributes
Generic)
instance ToJSON PresentationHintAttributes where
  toJSON :: PresentationHintAttributes -> Value
toJSON (PresentationHintAttributes String
x) = String -> Value
forall a. ToJSON a => a -> Value
toJSON String
x
  toJSON PresentationHintAttributes
hint = PresentationHintAttributes -> Value
forall a.
(Generic a, GToJSON Zero (Rep a), Typeable a) =>
a -> Value
genericToJSONWithModifier PresentationHintAttributes
hint
data PresentationHintKind
  = PresentationHintKindProperty
  | PresentationHintKindMethod
  | PresentationHintKindClass
  | PresentationHintKindData
  | PresentationHintKindEvent
  | PresentationHintKindBaseClass
  | PresentationHintKindInnerClass
  | PresentationHintKindInterface
  | PresentationHintKindMostDerivedClass
  | PresentationHintKindVirtual
  | PresentationHintKindDataBreakpoint
  | PresentationHintKind Text
  deriving stock (Int -> PresentationHintKind -> ShowS
[PresentationHintKind] -> ShowS
PresentationHintKind -> String
(Int -> PresentationHintKind -> ShowS)
-> (PresentationHintKind -> String)
-> ([PresentationHintKind] -> ShowS)
-> Show PresentationHintKind
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> PresentationHintKind -> ShowS
showsPrec :: Int -> PresentationHintKind -> ShowS
$cshow :: PresentationHintKind -> String
show :: PresentationHintKind -> String
$cshowList :: [PresentationHintKind] -> ShowS
showList :: [PresentationHintKind] -> ShowS
Show, PresentationHintKind -> PresentationHintKind -> Bool
(PresentationHintKind -> PresentationHintKind -> Bool)
-> (PresentationHintKind -> PresentationHintKind -> Bool)
-> Eq PresentationHintKind
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: PresentationHintKind -> PresentationHintKind -> Bool
== :: PresentationHintKind -> PresentationHintKind -> Bool
$c/= :: PresentationHintKind -> PresentationHintKind -> Bool
/= :: PresentationHintKind -> PresentationHintKind -> Bool
Eq, (forall x. PresentationHintKind -> Rep PresentationHintKind x)
-> (forall x. Rep PresentationHintKind x -> PresentationHintKind)
-> Generic PresentationHintKind
forall x. Rep PresentationHintKind x -> PresentationHintKind
forall x. PresentationHintKind -> Rep PresentationHintKind x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. PresentationHintKind -> Rep PresentationHintKind x
from :: forall x. PresentationHintKind -> Rep PresentationHintKind x
$cto :: forall x. Rep PresentationHintKind x -> PresentationHintKind
to :: forall x. Rep PresentationHintKind x -> PresentationHintKind
Generic)
instance ToJSON PresentationHintKind where
  toJSON :: PresentationHintKind -> Value
toJSON (PresentationHintKind Text
x) = Text -> Value
forall a. ToJSON a => a -> Value
toJSON Text
x
  toJSON PresentationHintKind
kind = PresentationHintKind -> Value
forall a.
(Generic a, GToJSON Zero (Rep a), Typeable a) =>
a -> Value
genericToJSONWithModifier PresentationHintKind
kind
data SetVariableResponse
  = SetVariableResponse
  { SetVariableResponse -> Text
setVariableResponseValue :: Text
    
    
    
  , SetVariableResponse -> Maybe Text
setVariableResponseType :: Maybe Text
    
    
    
    
  , SetVariableResponse -> Maybe Int
setVariableResponseReference :: Maybe Int
    
    
    
    
    
    
  , SetVariableResponse -> Maybe Int
setVariableResponseNamedVariables :: Maybe Int
    
    
    
    
    
    
  , SetVariableResponse -> Maybe Int
setVariableResponseIndexedVariables :: Maybe Int
    
    
    
    
    
    
   } deriving stock (Int -> SetVariableResponse -> ShowS
[SetVariableResponse] -> ShowS
SetVariableResponse -> String
(Int -> SetVariableResponse -> ShowS)
-> (SetVariableResponse -> String)
-> ([SetVariableResponse] -> ShowS)
-> Show SetVariableResponse
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SetVariableResponse -> ShowS
showsPrec :: Int -> SetVariableResponse -> ShowS
$cshow :: SetVariableResponse -> String
show :: SetVariableResponse -> String
$cshowList :: [SetVariableResponse] -> ShowS
showList :: [SetVariableResponse] -> ShowS
Show, SetVariableResponse -> SetVariableResponse -> Bool
(SetVariableResponse -> SetVariableResponse -> Bool)
-> (SetVariableResponse -> SetVariableResponse -> Bool)
-> Eq SetVariableResponse
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SetVariableResponse -> SetVariableResponse -> Bool
== :: SetVariableResponse -> SetVariableResponse -> Bool
$c/= :: SetVariableResponse -> SetVariableResponse -> Bool
/= :: SetVariableResponse -> SetVariableResponse -> Bool
Eq)
instance ToJSON SetVariableResponse where
  toJSON :: SetVariableResponse -> Value
toJSON SetVariableResponse {Maybe Int
Maybe Text
Text
setVariableResponseValue :: SetVariableResponse -> Text
setVariableResponseType :: SetVariableResponse -> Maybe Text
setVariableResponseReference :: SetVariableResponse -> Maybe Int
setVariableResponseNamedVariables :: SetVariableResponse -> Maybe Int
setVariableResponseIndexedVariables :: SetVariableResponse -> Maybe Int
setVariableResponseValue :: Text
setVariableResponseType :: Maybe Text
setVariableResponseReference :: Maybe Int
setVariableResponseNamedVariables :: Maybe Int
setVariableResponseIndexedVariables :: Maybe Int
..}
    = [Pair] -> Value
object
    [ Key
"value"            Key -> Text -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Text
setVariableResponseValue
    , Key
"type"             Key -> Maybe Text -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Maybe Text
setVariableResponseType
    , Key
"reference"        Key -> Maybe Int -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Maybe Int
setVariableResponseReference
    , Key
"variables"        Key -> Maybe Int -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Maybe Int
setVariableResponseNamedVariables
    , Key
"indexedVariables" Key -> Maybe Int -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Maybe Int
setVariableResponseIndexedVariables
    ]
data SourceResponse
  = SourceResponse
  { SourceResponse -> Text
sourceResponseContent :: Text
    
    
    
  , SourceResponse -> Maybe Text
sourceResponseMimeType :: Maybe Text
    
    
    
  } deriving stock (Int -> SourceResponse -> ShowS
[SourceResponse] -> ShowS
SourceResponse -> String
(Int -> SourceResponse -> ShowS)
-> (SourceResponse -> String)
-> ([SourceResponse] -> ShowS)
-> Show SourceResponse
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SourceResponse -> ShowS
showsPrec :: Int -> SourceResponse -> ShowS
$cshow :: SourceResponse -> String
show :: SourceResponse -> String
$cshowList :: [SourceResponse] -> ShowS
showList :: [SourceResponse] -> ShowS
Show, SourceResponse -> SourceResponse -> Bool
(SourceResponse -> SourceResponse -> Bool)
-> (SourceResponse -> SourceResponse -> Bool) -> Eq SourceResponse
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SourceResponse -> SourceResponse -> Bool
== :: SourceResponse -> SourceResponse -> Bool
$c/= :: SourceResponse -> SourceResponse -> Bool
/= :: SourceResponse -> SourceResponse -> Bool
Eq)
instance ToJSON SourceResponse where
  toJSON :: SourceResponse -> Value
toJSON SourceResponse {Maybe Text
Text
sourceResponseContent :: SourceResponse -> Text
sourceResponseMimeType :: SourceResponse -> Maybe Text
sourceResponseContent :: Text
sourceResponseMimeType :: Maybe Text
..}
    = [Pair] -> Value
object
    [ Key
"content"  Key -> Text -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Text
sourceResponseContent
    , Key
"mimeType" Key -> Maybe Text -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Maybe Text
sourceResponseMimeType
    ]
newtype ThreadsResponse
  = ThreadsResponse
  { ThreadsResponse -> [Thread]
threads :: [Thread]
    
    
    
  } deriving stock (Int -> ThreadsResponse -> ShowS
[ThreadsResponse] -> ShowS
ThreadsResponse -> String
(Int -> ThreadsResponse -> ShowS)
-> (ThreadsResponse -> String)
-> ([ThreadsResponse] -> ShowS)
-> Show ThreadsResponse
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ThreadsResponse -> ShowS
showsPrec :: Int -> ThreadsResponse -> ShowS
$cshow :: ThreadsResponse -> String
show :: ThreadsResponse -> String
$cshowList :: [ThreadsResponse] -> ShowS
showList :: [ThreadsResponse] -> ShowS
Show, ThreadsResponse -> ThreadsResponse -> Bool
(ThreadsResponse -> ThreadsResponse -> Bool)
-> (ThreadsResponse -> ThreadsResponse -> Bool)
-> Eq ThreadsResponse
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ThreadsResponse -> ThreadsResponse -> Bool
== :: ThreadsResponse -> ThreadsResponse -> Bool
$c/= :: ThreadsResponse -> ThreadsResponse -> Bool
/= :: ThreadsResponse -> ThreadsResponse -> Bool
Eq)
instance ToJSON ThreadsResponse where
  toJSON :: ThreadsResponse -> Value
toJSON (ThreadsResponse [Thread]
ts)
    = [Pair] -> Value
object
    [ Key
"threads" Key -> [Thread] -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= [Thread]
ts
    ]
data LoadedSourcesResponse
  = LoadedSourcesResponse
  { LoadedSourcesResponse -> [Source]
loadedSourcesResponseSources :: [Source]
    
    
    
  } deriving stock (Int -> LoadedSourcesResponse -> ShowS
[LoadedSourcesResponse] -> ShowS
LoadedSourcesResponse -> String
(Int -> LoadedSourcesResponse -> ShowS)
-> (LoadedSourcesResponse -> String)
-> ([LoadedSourcesResponse] -> ShowS)
-> Show LoadedSourcesResponse
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> LoadedSourcesResponse -> ShowS
showsPrec :: Int -> LoadedSourcesResponse -> ShowS
$cshow :: LoadedSourcesResponse -> String
show :: LoadedSourcesResponse -> String
$cshowList :: [LoadedSourcesResponse] -> ShowS
showList :: [LoadedSourcesResponse] -> ShowS
Show, LoadedSourcesResponse -> LoadedSourcesResponse -> Bool
(LoadedSourcesResponse -> LoadedSourcesResponse -> Bool)
-> (LoadedSourcesResponse -> LoadedSourcesResponse -> Bool)
-> Eq LoadedSourcesResponse
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: LoadedSourcesResponse -> LoadedSourcesResponse -> Bool
== :: LoadedSourcesResponse -> LoadedSourcesResponse -> Bool
$c/= :: LoadedSourcesResponse -> LoadedSourcesResponse -> Bool
/= :: LoadedSourcesResponse -> LoadedSourcesResponse -> Bool
Eq)
instance ToJSON LoadedSourcesResponse where
  toJSON :: LoadedSourcesResponse -> Value
toJSON LoadedSourcesResponse {[Source]
loadedSourcesResponseSources :: LoadedSourcesResponse -> [Source]
loadedSourcesResponseSources :: [Source]
..}
    = [Pair] -> Value
object
    [ Key
"sources" Key -> [Source] -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= [Source]
loadedSourcesResponseSources
    ]
data EvaluateResponse
  = EvaluateResponse
  { EvaluateResponse -> Text
evaluateResponseResult :: Text
    
    
    
  , EvaluateResponse -> Text
evaluateResponseType :: Text
    
    
    
    
    
  , EvaluateResponse -> Maybe VariablePresentationHint
evaluateResponsePresentationHint :: Maybe VariablePresentationHint
    
    
    
    
  , EvaluateResponse -> Int
evaluateResponseVariablesReference :: Int
    
    
    
    
    
    
  , EvaluateResponse -> Maybe Int
evaluateResponseNamedVariables :: Maybe Int
    
    
    
    
    
    
  , EvaluateResponse -> Maybe Int
evaluateResponseIndexedVariables :: Maybe Int
    
    
    
    
    
    
  , EvaluateResponse -> Maybe Text
evaluateResponseMemoryReference :: Maybe Text
    
    
    
    
    
    
    
  } deriving stock (Int -> EvaluateResponse -> ShowS
[EvaluateResponse] -> ShowS
EvaluateResponse -> String
(Int -> EvaluateResponse -> ShowS)
-> (EvaluateResponse -> String)
-> ([EvaluateResponse] -> ShowS)
-> Show EvaluateResponse
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> EvaluateResponse -> ShowS
showsPrec :: Int -> EvaluateResponse -> ShowS
$cshow :: EvaluateResponse -> String
show :: EvaluateResponse -> String
$cshowList :: [EvaluateResponse] -> ShowS
showList :: [EvaluateResponse] -> ShowS
Show, EvaluateResponse -> EvaluateResponse -> Bool
(EvaluateResponse -> EvaluateResponse -> Bool)
-> (EvaluateResponse -> EvaluateResponse -> Bool)
-> Eq EvaluateResponse
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: EvaluateResponse -> EvaluateResponse -> Bool
== :: EvaluateResponse -> EvaluateResponse -> Bool
$c/= :: EvaluateResponse -> EvaluateResponse -> Bool
/= :: EvaluateResponse -> EvaluateResponse -> Bool
Eq, (forall x. EvaluateResponse -> Rep EvaluateResponse x)
-> (forall x. Rep EvaluateResponse x -> EvaluateResponse)
-> Generic EvaluateResponse
forall x. Rep EvaluateResponse x -> EvaluateResponse
forall x. EvaluateResponse -> Rep EvaluateResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. EvaluateResponse -> Rep EvaluateResponse x
from :: forall x. EvaluateResponse -> Rep EvaluateResponse x
$cto :: forall x. Rep EvaluateResponse x -> EvaluateResponse
to :: forall x. Rep EvaluateResponse x -> EvaluateResponse
Generic)
instance ToJSON EvaluateResponse where
  toJSON :: EvaluateResponse -> Value
toJSON = EvaluateResponse -> Value
forall a.
(Generic a, GToJSON Zero (Rep a), Typeable a) =>
a -> Value
genericToJSONWithModifier
data SetExpressionResponse
  = SetExpressionResponse
  { SetExpressionResponse -> Text
setExpressionResponseValue :: Text
    
    
    
  , SetExpressionResponse -> Maybe Text
setExpressionResponseType :: Maybe Text
    
    
    
    
    
  , SetExpressionResponse -> Maybe VariablePresentationHint
setExpressionResponsePresentationHint :: Maybe VariablePresentationHint
    
    
    
    
  , SetExpressionResponse -> Maybe Int
setExpressionResponseVariablesReference:: Maybe Int
    
    
    
    
    
    
  , SetExpressionResponse -> Maybe Int
setExpressionResponseNamedVariables:: Maybe Int
    
    
    
    
    
    
  , SetExpressionResponse -> Maybe Int
setExpressionResponseIndexedVariables:: Maybe Int
    
    
    
    
    
    
  } deriving stock (Int -> SetExpressionResponse -> ShowS
[SetExpressionResponse] -> ShowS
SetExpressionResponse -> String
(Int -> SetExpressionResponse -> ShowS)
-> (SetExpressionResponse -> String)
-> ([SetExpressionResponse] -> ShowS)
-> Show SetExpressionResponse
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SetExpressionResponse -> ShowS
showsPrec :: Int -> SetExpressionResponse -> ShowS
$cshow :: SetExpressionResponse -> String
show :: SetExpressionResponse -> String
$cshowList :: [SetExpressionResponse] -> ShowS
showList :: [SetExpressionResponse] -> ShowS
Show, SetExpressionResponse -> SetExpressionResponse -> Bool
(SetExpressionResponse -> SetExpressionResponse -> Bool)
-> (SetExpressionResponse -> SetExpressionResponse -> Bool)
-> Eq SetExpressionResponse
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SetExpressionResponse -> SetExpressionResponse -> Bool
== :: SetExpressionResponse -> SetExpressionResponse -> Bool
$c/= :: SetExpressionResponse -> SetExpressionResponse -> Bool
/= :: SetExpressionResponse -> SetExpressionResponse -> Bool
Eq, (forall x. SetExpressionResponse -> Rep SetExpressionResponse x)
-> (forall x. Rep SetExpressionResponse x -> SetExpressionResponse)
-> Generic SetExpressionResponse
forall x. Rep SetExpressionResponse x -> SetExpressionResponse
forall x. SetExpressionResponse -> Rep SetExpressionResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. SetExpressionResponse -> Rep SetExpressionResponse x
from :: forall x. SetExpressionResponse -> Rep SetExpressionResponse x
$cto :: forall x. Rep SetExpressionResponse x -> SetExpressionResponse
to :: forall x. Rep SetExpressionResponse x -> SetExpressionResponse
Generic)
instance ToJSON SetExpressionResponse where
  toJSON :: SetExpressionResponse -> Value
toJSON = SetExpressionResponse -> Value
forall a.
(Generic a, GToJSON Zero (Rep a), Typeable a) =>
a -> Value
genericToJSONWithModifier
data StepInTargetsResponse
  = StepInTargetsResponse
  { StepInTargetsResponse -> [StepInTarget]
stepInTargetsResponseTargets :: [StepInTarget]
    
    
    
  } deriving stock (Int -> StepInTargetsResponse -> ShowS
[StepInTargetsResponse] -> ShowS
StepInTargetsResponse -> String
(Int -> StepInTargetsResponse -> ShowS)
-> (StepInTargetsResponse -> String)
-> ([StepInTargetsResponse] -> ShowS)
-> Show StepInTargetsResponse
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> StepInTargetsResponse -> ShowS
showsPrec :: Int -> StepInTargetsResponse -> ShowS
$cshow :: StepInTargetsResponse -> String
show :: StepInTargetsResponse -> String
$cshowList :: [StepInTargetsResponse] -> ShowS
showList :: [StepInTargetsResponse] -> ShowS
Show, StepInTargetsResponse -> StepInTargetsResponse -> Bool
(StepInTargetsResponse -> StepInTargetsResponse -> Bool)
-> (StepInTargetsResponse -> StepInTargetsResponse -> Bool)
-> Eq StepInTargetsResponse
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: StepInTargetsResponse -> StepInTargetsResponse -> Bool
== :: StepInTargetsResponse -> StepInTargetsResponse -> Bool
$c/= :: StepInTargetsResponse -> StepInTargetsResponse -> Bool
/= :: StepInTargetsResponse -> StepInTargetsResponse -> Bool
Eq, (forall x. StepInTargetsResponse -> Rep StepInTargetsResponse x)
-> (forall x. Rep StepInTargetsResponse x -> StepInTargetsResponse)
-> Generic StepInTargetsResponse
forall x. Rep StepInTargetsResponse x -> StepInTargetsResponse
forall x. StepInTargetsResponse -> Rep StepInTargetsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. StepInTargetsResponse -> Rep StepInTargetsResponse x
from :: forall x. StepInTargetsResponse -> Rep StepInTargetsResponse x
$cto :: forall x. Rep StepInTargetsResponse x -> StepInTargetsResponse
to :: forall x. Rep StepInTargetsResponse x -> StepInTargetsResponse
Generic)
instance ToJSON StepInTargetsResponse where
  toJSON :: StepInTargetsResponse -> Value
toJSON = StepInTargetsResponse -> Value
forall a.
(Generic a, GToJSON Zero (Rep a), Typeable a) =>
a -> Value
genericToJSONWithModifier
data StepInTarget
  = StepInTarget
  { StepInTarget -> Int
stepInTargetId :: Int
    
    
    
  , StepInTarget -> Text
stepInTargetLabel :: Text
    
    
    
  , StepInTarget -> Maybe Int
stepInTargetLine :: Maybe Int
    
    
    
  , StepInTarget -> Maybe Int
stepInTargetColumn :: Maybe Int
    
    
    
    
    
  , StepInTarget -> Maybe Int
stepInTargetEndLine :: Maybe Int
    
    
    
  , StepInTarget -> Maybe Int
stepInTargetEndColumn :: Maybe Int
    
    
    
    
  } deriving stock (Int -> StepInTarget -> ShowS
[StepInTarget] -> ShowS
StepInTarget -> String
(Int -> StepInTarget -> ShowS)
-> (StepInTarget -> String)
-> ([StepInTarget] -> ShowS)
-> Show StepInTarget
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> StepInTarget -> ShowS
showsPrec :: Int -> StepInTarget -> ShowS
$cshow :: StepInTarget -> String
show :: StepInTarget -> String
$cshowList :: [StepInTarget] -> ShowS
showList :: [StepInTarget] -> ShowS
Show, StepInTarget -> StepInTarget -> Bool
(StepInTarget -> StepInTarget -> Bool)
-> (StepInTarget -> StepInTarget -> Bool) -> Eq StepInTarget
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: StepInTarget -> StepInTarget -> Bool
== :: StepInTarget -> StepInTarget -> Bool
$c/= :: StepInTarget -> StepInTarget -> Bool
/= :: StepInTarget -> StepInTarget -> Bool
Eq, (forall x. StepInTarget -> Rep StepInTarget x)
-> (forall x. Rep StepInTarget x -> StepInTarget)
-> Generic StepInTarget
forall x. Rep StepInTarget x -> StepInTarget
forall x. StepInTarget -> Rep StepInTarget x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. StepInTarget -> Rep StepInTarget x
from :: forall x. StepInTarget -> Rep StepInTarget x
$cto :: forall x. Rep StepInTarget x -> StepInTarget
to :: forall x. Rep StepInTarget x -> StepInTarget
Generic)
defaultStepInTarget :: StepInTarget
defaultStepInTarget :: StepInTarget
defaultStepInTarget
  = StepInTarget
  { stepInTargetId :: Int
stepInTargetId = Int
0
  , stepInTargetLabel :: Text
stepInTargetLabel = Text
forall a. Monoid a => a
mempty
  , stepInTargetLine :: Maybe Int
stepInTargetLine = Maybe Int
forall a. Maybe a
Nothing
  , stepInTargetColumn :: Maybe Int
stepInTargetColumn = Maybe Int
forall a. Maybe a
Nothing
  , stepInTargetEndLine :: Maybe Int
stepInTargetEndLine = Maybe Int
forall a. Maybe a
Nothing
  , stepInTargetEndColumn :: Maybe Int
stepInTargetEndColumn = Maybe Int
forall a. Maybe a
Nothing
  }
instance ToJSON StepInTarget where
  toJSON :: StepInTarget -> Value
toJSON = StepInTarget -> Value
forall a.
(Generic a, GToJSON Zero (Rep a), Typeable a) =>
a -> Value
genericToJSONWithModifier
data GotoTargetsResponse
  = GotoTargetsResponse
  { GotoTargetsResponse -> [GotoTarget]
goToTargetsResponseTargets :: [GotoTarget]
    
    
    
  } deriving stock (Int -> GotoTargetsResponse -> ShowS
[GotoTargetsResponse] -> ShowS
GotoTargetsResponse -> String
(Int -> GotoTargetsResponse -> ShowS)
-> (GotoTargetsResponse -> String)
-> ([GotoTargetsResponse] -> ShowS)
-> Show GotoTargetsResponse
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> GotoTargetsResponse -> ShowS
showsPrec :: Int -> GotoTargetsResponse -> ShowS
$cshow :: GotoTargetsResponse -> String
show :: GotoTargetsResponse -> String
$cshowList :: [GotoTargetsResponse] -> ShowS
showList :: [GotoTargetsResponse] -> ShowS
Show, GotoTargetsResponse -> GotoTargetsResponse -> Bool
(GotoTargetsResponse -> GotoTargetsResponse -> Bool)
-> (GotoTargetsResponse -> GotoTargetsResponse -> Bool)
-> Eq GotoTargetsResponse
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: GotoTargetsResponse -> GotoTargetsResponse -> Bool
== :: GotoTargetsResponse -> GotoTargetsResponse -> Bool
$c/= :: GotoTargetsResponse -> GotoTargetsResponse -> Bool
/= :: GotoTargetsResponse -> GotoTargetsResponse -> Bool
Eq, (forall x. GotoTargetsResponse -> Rep GotoTargetsResponse x)
-> (forall x. Rep GotoTargetsResponse x -> GotoTargetsResponse)
-> Generic GotoTargetsResponse
forall x. Rep GotoTargetsResponse x -> GotoTargetsResponse
forall x. GotoTargetsResponse -> Rep GotoTargetsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. GotoTargetsResponse -> Rep GotoTargetsResponse x
from :: forall x. GotoTargetsResponse -> Rep GotoTargetsResponse x
$cto :: forall x. Rep GotoTargetsResponse x -> GotoTargetsResponse
to :: forall x. Rep GotoTargetsResponse x -> GotoTargetsResponse
Generic)
instance ToJSON GotoTargetsResponse where
  toJSON :: GotoTargetsResponse -> Value
toJSON = GotoTargetsResponse -> Value
forall a.
(Generic a, GToJSON Zero (Rep a), Typeable a) =>
a -> Value
genericToJSONWithModifier
data GotoTarget
  = GotoTarget
  { GotoTarget -> Int
gotoTargetId :: Int
    
    
  , GotoTarget -> String
gotoTargetLabel :: String
    
    
    
  , GotoTarget -> Int
gotoTargetLine :: Int
    
    
    
  , GotoTarget -> Maybe Int
gotoTargetColumn :: Maybe Int
    
    
    
  , GotoTarget -> Maybe Int
gotoTargetEndLine :: Maybe Int
    
    
    
  , GotoTarget -> Maybe Int
gotoTargetEndColumn :: Maybe Int
    
    
    
  , GotoTarget -> Maybe String
gotoTargetInstructionPointerReference :: Maybe String
    
    
    
    
  } deriving stock (Int -> GotoTarget -> ShowS
[GotoTarget] -> ShowS
GotoTarget -> String
(Int -> GotoTarget -> ShowS)
-> (GotoTarget -> String)
-> ([GotoTarget] -> ShowS)
-> Show GotoTarget
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> GotoTarget -> ShowS
showsPrec :: Int -> GotoTarget -> ShowS
$cshow :: GotoTarget -> String
show :: GotoTarget -> String
$cshowList :: [GotoTarget] -> ShowS
showList :: [GotoTarget] -> ShowS
Show, GotoTarget -> GotoTarget -> Bool
(GotoTarget -> GotoTarget -> Bool)
-> (GotoTarget -> GotoTarget -> Bool) -> Eq GotoTarget
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: GotoTarget -> GotoTarget -> Bool
== :: GotoTarget -> GotoTarget -> Bool
$c/= :: GotoTarget -> GotoTarget -> Bool
/= :: GotoTarget -> GotoTarget -> Bool
Eq, (forall x. GotoTarget -> Rep GotoTarget x)
-> (forall x. Rep GotoTarget x -> GotoTarget) -> Generic GotoTarget
forall x. Rep GotoTarget x -> GotoTarget
forall x. GotoTarget -> Rep GotoTarget x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. GotoTarget -> Rep GotoTarget x
from :: forall x. GotoTarget -> Rep GotoTarget x
$cto :: forall x. Rep GotoTarget x -> GotoTarget
to :: forall x. Rep GotoTarget x -> GotoTarget
Generic)
defaultGotoTarget :: GotoTarget
defaultGotoTarget :: GotoTarget
defaultGotoTarget
  = GotoTarget
  { gotoTargetId :: Int
gotoTargetId = Int
0
  , gotoTargetLabel :: String
gotoTargetLabel = String
forall a. Monoid a => a
mempty
  , gotoTargetLine :: Int
gotoTargetLine = Int
0
  , gotoTargetColumn :: Maybe Int
gotoTargetColumn = Maybe Int
forall a. Maybe a
Nothing
  , gotoTargetEndLine :: Maybe Int
gotoTargetEndLine = Maybe Int
forall a. Maybe a
Nothing
  , gotoTargetEndColumn :: Maybe Int
gotoTargetEndColumn = Maybe Int
forall a. Maybe a
Nothing
  , gotoTargetInstructionPointerReference :: Maybe String
gotoTargetInstructionPointerReference = Maybe String
forall a. Maybe a
Nothing
  }
instance ToJSON GotoTarget where
  toJSON :: GotoTarget -> Value
toJSON = GotoTarget -> Value
forall a.
(Generic a, GToJSON Zero (Rep a), Typeable a) =>
a -> Value
genericToJSONWithModifier
data CompletionsResponse
  = CompletionsResponse
  { CompletionsResponse -> [CompletionItem]
completionResponseTargets :: [CompletionItem]
    
    
    
  } deriving stock (Int -> CompletionsResponse -> ShowS
[CompletionsResponse] -> ShowS
CompletionsResponse -> String
(Int -> CompletionsResponse -> ShowS)
-> (CompletionsResponse -> String)
-> ([CompletionsResponse] -> ShowS)
-> Show CompletionsResponse
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CompletionsResponse -> ShowS
showsPrec :: Int -> CompletionsResponse -> ShowS
$cshow :: CompletionsResponse -> String
show :: CompletionsResponse -> String
$cshowList :: [CompletionsResponse] -> ShowS
showList :: [CompletionsResponse] -> ShowS
Show, CompletionsResponse -> CompletionsResponse -> Bool
(CompletionsResponse -> CompletionsResponse -> Bool)
-> (CompletionsResponse -> CompletionsResponse -> Bool)
-> Eq CompletionsResponse
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CompletionsResponse -> CompletionsResponse -> Bool
== :: CompletionsResponse -> CompletionsResponse -> Bool
$c/= :: CompletionsResponse -> CompletionsResponse -> Bool
/= :: CompletionsResponse -> CompletionsResponse -> Bool
Eq, (forall x. CompletionsResponse -> Rep CompletionsResponse x)
-> (forall x. Rep CompletionsResponse x -> CompletionsResponse)
-> Generic CompletionsResponse
forall x. Rep CompletionsResponse x -> CompletionsResponse
forall x. CompletionsResponse -> Rep CompletionsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. CompletionsResponse -> Rep CompletionsResponse x
from :: forall x. CompletionsResponse -> Rep CompletionsResponse x
$cto :: forall x. Rep CompletionsResponse x -> CompletionsResponse
to :: forall x. Rep CompletionsResponse x -> CompletionsResponse
Generic)
instance ToJSON CompletionsResponse where
  toJSON :: CompletionsResponse -> Value
toJSON = CompletionsResponse -> Value
forall a.
(Generic a, GToJSON Zero (Rep a), Typeable a) =>
a -> Value
genericToJSONWithModifier
data CompletionItem
  = CompletionItem
  { CompletionItem -> String
completionItemLabel :: String
    
    
    
    
  , CompletionItem -> Maybe String
completionItemText :: Maybe String
    
    
    
    
  , CompletionItem -> Maybe String
completionItemSortText :: Maybe String
    
    
    
    
  , CompletionItem -> Maybe String
completionItemDetail :: Maybe String
    
    
    
    
  , CompletionItem -> Maybe CompletionItemType
completionItemType :: Maybe CompletionItemType
    
    
    
    
  , CompletionItem -> Maybe Int
completionItemTypeStart :: Maybe Int
    
    
    
    
    
    
    
  , CompletionItem -> Maybe Int
completionItemTypeLength :: Maybe Int
    
    
    
    
    
  , CompletionItem -> Maybe Int
completionItemTypeSelectionStart :: Maybe Int
    
    
    
    
    
    
  , CompletionItem -> Maybe Int
completionItemTypeSelectionLength :: Maybe Int
    
    
    
    
    
    
  } deriving stock (Int -> CompletionItem -> ShowS
[CompletionItem] -> ShowS
CompletionItem -> String
(Int -> CompletionItem -> ShowS)
-> (CompletionItem -> String)
-> ([CompletionItem] -> ShowS)
-> Show CompletionItem
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CompletionItem -> ShowS
showsPrec :: Int -> CompletionItem -> ShowS
$cshow :: CompletionItem -> String
show :: CompletionItem -> String
$cshowList :: [CompletionItem] -> ShowS
showList :: [CompletionItem] -> ShowS
Show, CompletionItem -> CompletionItem -> Bool
(CompletionItem -> CompletionItem -> Bool)
-> (CompletionItem -> CompletionItem -> Bool) -> Eq CompletionItem
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CompletionItem -> CompletionItem -> Bool
== :: CompletionItem -> CompletionItem -> Bool
$c/= :: CompletionItem -> CompletionItem -> Bool
/= :: CompletionItem -> CompletionItem -> Bool
Eq, (forall x. CompletionItem -> Rep CompletionItem x)
-> (forall x. Rep CompletionItem x -> CompletionItem)
-> Generic CompletionItem
forall x. Rep CompletionItem x -> CompletionItem
forall x. CompletionItem -> Rep CompletionItem x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. CompletionItem -> Rep CompletionItem x
from :: forall x. CompletionItem -> Rep CompletionItem x
$cto :: forall x. Rep CompletionItem x -> CompletionItem
to :: forall x. Rep CompletionItem x -> CompletionItem
Generic)
defaultCompletionItem :: CompletionItem
defaultCompletionItem :: CompletionItem
defaultCompletionItem
  = CompletionItem
  { completionItemLabel :: String
completionItemLabel = String
forall a. Monoid a => a
mempty
  , completionItemText :: Maybe String
completionItemText = Maybe String
forall a. Maybe a
Nothing
  , completionItemSortText :: Maybe String
completionItemSortText = Maybe String
forall a. Maybe a
Nothing
  , completionItemDetail :: Maybe String
completionItemDetail = Maybe String
forall a. Maybe a
Nothing
  , completionItemType :: Maybe CompletionItemType
completionItemType = Maybe CompletionItemType
forall a. Maybe a
Nothing
  , completionItemTypeStart :: Maybe Int
completionItemTypeStart = Maybe Int
forall a. Maybe a
Nothing
  , completionItemTypeLength :: Maybe Int
completionItemTypeLength = Maybe Int
forall a. Maybe a
Nothing
  , completionItemTypeSelectionStart :: Maybe Int
completionItemTypeSelectionStart = Maybe Int
forall a. Maybe a
Nothing
  , completionItemTypeSelectionLength :: Maybe Int
completionItemTypeSelectionLength = Maybe Int
forall a. Maybe a
Nothing
  }
instance ToJSON CompletionItem where
  toJSON :: CompletionItem -> Value
toJSON = CompletionItem -> Value
forall a.
(Generic a, GToJSON Zero (Rep a), Typeable a) =>
a -> Value
genericToJSONWithModifier
instance ToJSON CompletionItemType where
  toJSON :: CompletionItemType -> Value
toJSON = CompletionItemType -> Value
forall a.
(Generic a, GToJSON Zero (Rep a), Typeable a) =>
a -> Value
genericToJSONWithModifier
data ExceptionInfoResponse
  = ExceptionInfoResponse
  { ExceptionInfoResponse -> Text
exceptionInfoResponseId :: Text
    
    
    
  , ExceptionInfoResponse -> Maybe Text
exceptionInfoDescriptionId :: Maybe Text
    
    
    
  , ExceptionInfoResponse -> ExceptionBreakMode
exceptionInfoBreakMode :: ExceptionBreakMode
    
    
    
  , ExceptionInfoResponse -> Maybe ExceptionDetails
exceptionInfoReponseDetails :: Maybe ExceptionDetails
    
    
    
  } deriving stock (Int -> ExceptionInfoResponse -> ShowS
[ExceptionInfoResponse] -> ShowS
ExceptionInfoResponse -> String
(Int -> ExceptionInfoResponse -> ShowS)
-> (ExceptionInfoResponse -> String)
-> ([ExceptionInfoResponse] -> ShowS)
-> Show ExceptionInfoResponse
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ExceptionInfoResponse -> ShowS
showsPrec :: Int -> ExceptionInfoResponse -> ShowS
$cshow :: ExceptionInfoResponse -> String
show :: ExceptionInfoResponse -> String
$cshowList :: [ExceptionInfoResponse] -> ShowS
showList :: [ExceptionInfoResponse] -> ShowS
Show, ExceptionInfoResponse -> ExceptionInfoResponse -> Bool
(ExceptionInfoResponse -> ExceptionInfoResponse -> Bool)
-> (ExceptionInfoResponse -> ExceptionInfoResponse -> Bool)
-> Eq ExceptionInfoResponse
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ExceptionInfoResponse -> ExceptionInfoResponse -> Bool
== :: ExceptionInfoResponse -> ExceptionInfoResponse -> Bool
$c/= :: ExceptionInfoResponse -> ExceptionInfoResponse -> Bool
/= :: ExceptionInfoResponse -> ExceptionInfoResponse -> Bool
Eq, (forall x. ExceptionInfoResponse -> Rep ExceptionInfoResponse x)
-> (forall x. Rep ExceptionInfoResponse x -> ExceptionInfoResponse)
-> Generic ExceptionInfoResponse
forall x. Rep ExceptionInfoResponse x -> ExceptionInfoResponse
forall x. ExceptionInfoResponse -> Rep ExceptionInfoResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ExceptionInfoResponse -> Rep ExceptionInfoResponse x
from :: forall x. ExceptionInfoResponse -> Rep ExceptionInfoResponse x
$cto :: forall x. Rep ExceptionInfoResponse x -> ExceptionInfoResponse
to :: forall x. Rep ExceptionInfoResponse x -> ExceptionInfoResponse
Generic)
instance ToJSON ExceptionInfoResponse where
  toJSON :: ExceptionInfoResponse -> Value
toJSON = ExceptionInfoResponse -> Value
forall a.
(Generic a, GToJSON Zero (Rep a), Typeable a) =>
a -> Value
genericToJSONWithModifier
data ExceptionBreakMode
  = Never
  | Always
  | Unhandled
  | UserUnhandled
  deriving stock (Int -> ExceptionBreakMode -> ShowS
[ExceptionBreakMode] -> ShowS
ExceptionBreakMode -> String
(Int -> ExceptionBreakMode -> ShowS)
-> (ExceptionBreakMode -> String)
-> ([ExceptionBreakMode] -> ShowS)
-> Show ExceptionBreakMode
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ExceptionBreakMode -> ShowS
showsPrec :: Int -> ExceptionBreakMode -> ShowS
$cshow :: ExceptionBreakMode -> String
show :: ExceptionBreakMode -> String
$cshowList :: [ExceptionBreakMode] -> ShowS
showList :: [ExceptionBreakMode] -> ShowS
Show, ExceptionBreakMode -> ExceptionBreakMode -> Bool
(ExceptionBreakMode -> ExceptionBreakMode -> Bool)
-> (ExceptionBreakMode -> ExceptionBreakMode -> Bool)
-> Eq ExceptionBreakMode
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ExceptionBreakMode -> ExceptionBreakMode -> Bool
== :: ExceptionBreakMode -> ExceptionBreakMode -> Bool
$c/= :: ExceptionBreakMode -> ExceptionBreakMode -> Bool
/= :: ExceptionBreakMode -> ExceptionBreakMode -> Bool
Eq, (forall x. ExceptionBreakMode -> Rep ExceptionBreakMode x)
-> (forall x. Rep ExceptionBreakMode x -> ExceptionBreakMode)
-> Generic ExceptionBreakMode
forall x. Rep ExceptionBreakMode x -> ExceptionBreakMode
forall x. ExceptionBreakMode -> Rep ExceptionBreakMode x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ExceptionBreakMode -> Rep ExceptionBreakMode x
from :: forall x. ExceptionBreakMode -> Rep ExceptionBreakMode x
$cto :: forall x. Rep ExceptionBreakMode x -> ExceptionBreakMode
to :: forall x. Rep ExceptionBreakMode x -> ExceptionBreakMode
Generic)
instance ToJSON ExceptionBreakMode where
  toJSON :: ExceptionBreakMode -> Value
toJSON ExceptionBreakMode
Never         = Value
"never"
  toJSON ExceptionBreakMode
Always        = Value
"always"
  toJSON ExceptionBreakMode
Unhandled     = Value
"unhandled"
  toJSON ExceptionBreakMode
UserUnhandled = Value
"userUnhandled"
instance FromJSON ExceptionBreakMode where
  parseJSON :: Value -> Parser ExceptionBreakMode
parseJSON = Value -> Parser ExceptionBreakMode
forall a.
(Generic a, GFromJSON Zero (Rep a), Typeable a) =>
Value -> Parser a
genericParseJSONWithModifier
data ExceptionDetails
  = ExceptionDetails
  { ExceptionDetails -> Maybe String
exceptionDetailsMessage :: Maybe String
    
    
    
  , ExceptionDetails -> Maybe Text
exceptionDetailstypeName :: Maybe Text
    
    
    
  , ExceptionDetails -> Maybe Text
exceptionDetailsFullTypeName :: Maybe Text
    
    
    
  , ExceptionDetails -> Maybe Text
exceptionDetailsEvaluateName :: Maybe Text
    
    
    
    
  , ExceptionDetails -> Maybe Text
exceptionDetailsStackTrace :: Maybe Text
    
    
    
  , ExceptionDetails -> Maybe [ExceptionDetails]
exceptionDetailsInnerException :: Maybe [ExceptionDetails]
    
    
    
  } deriving stock (Int -> ExceptionDetails -> ShowS
[ExceptionDetails] -> ShowS
ExceptionDetails -> String
(Int -> ExceptionDetails -> ShowS)
-> (ExceptionDetails -> String)
-> ([ExceptionDetails] -> ShowS)
-> Show ExceptionDetails
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ExceptionDetails -> ShowS
showsPrec :: Int -> ExceptionDetails -> ShowS
$cshow :: ExceptionDetails -> String
show :: ExceptionDetails -> String
$cshowList :: [ExceptionDetails] -> ShowS
showList :: [ExceptionDetails] -> ShowS
Show, ExceptionDetails -> ExceptionDetails -> Bool
(ExceptionDetails -> ExceptionDetails -> Bool)
-> (ExceptionDetails -> ExceptionDetails -> Bool)
-> Eq ExceptionDetails
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ExceptionDetails -> ExceptionDetails -> Bool
== :: ExceptionDetails -> ExceptionDetails -> Bool
$c/= :: ExceptionDetails -> ExceptionDetails -> Bool
/= :: ExceptionDetails -> ExceptionDetails -> Bool
Eq, (forall x. ExceptionDetails -> Rep ExceptionDetails x)
-> (forall x. Rep ExceptionDetails x -> ExceptionDetails)
-> Generic ExceptionDetails
forall x. Rep ExceptionDetails x -> ExceptionDetails
forall x. ExceptionDetails -> Rep ExceptionDetails x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ExceptionDetails -> Rep ExceptionDetails x
from :: forall x. ExceptionDetails -> Rep ExceptionDetails x
$cto :: forall x. Rep ExceptionDetails x -> ExceptionDetails
to :: forall x. Rep ExceptionDetails x -> ExceptionDetails
Generic)
defaultExceptionDetails :: ExceptionDetails
defaultExceptionDetails :: ExceptionDetails
defaultExceptionDetails
  = ExceptionDetails
  { exceptionDetailsMessage :: Maybe String
exceptionDetailsMessage = Maybe String
forall a. Maybe a
Nothing
  , exceptionDetailstypeName :: Maybe Text
exceptionDetailstypeName = Maybe Text
forall a. Maybe a
Nothing
  , exceptionDetailsFullTypeName :: Maybe Text
exceptionDetailsFullTypeName = Maybe Text
forall a. Maybe a
Nothing
  , exceptionDetailsEvaluateName :: Maybe Text
exceptionDetailsEvaluateName = Maybe Text
forall a. Maybe a
Nothing
  , exceptionDetailsStackTrace :: Maybe Text
exceptionDetailsStackTrace = Maybe Text
forall a. Maybe a
Nothing
  , exceptionDetailsInnerException :: Maybe [ExceptionDetails]
exceptionDetailsInnerException = Maybe [ExceptionDetails]
forall a. Maybe a
Nothing
  }
instance ToJSON ExceptionDetails where
  toJSON :: ExceptionDetails -> Value
toJSON = ExceptionDetails -> Value
forall a.
(Generic a, GToJSON Zero (Rep a), Typeable a) =>
a -> Value
genericToJSONWithModifier
data ReadMemoryResponse
  = ReadMemoryResponse
  { ReadMemoryResponse -> Int
readMemoryResponseBody :: Int
    
    
    
    
    
  , ReadMemoryResponse -> Text
readMemoryResponseAddress :: Text
    
    
    
    
    
    
  , ReadMemoryResponse -> Maybe Int
readMemoryResponseUnreadableBytes:: Maybe Int
    
    
    
    
    
    
  , ReadMemoryResponse -> Maybe Text
readMemoryResponseData :: Maybe Text
  } deriving stock (Int -> ReadMemoryResponse -> ShowS
[ReadMemoryResponse] -> ShowS
ReadMemoryResponse -> String
(Int -> ReadMemoryResponse -> ShowS)
-> (ReadMemoryResponse -> String)
-> ([ReadMemoryResponse] -> ShowS)
-> Show ReadMemoryResponse
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ReadMemoryResponse -> ShowS
showsPrec :: Int -> ReadMemoryResponse -> ShowS
$cshow :: ReadMemoryResponse -> String
show :: ReadMemoryResponse -> String
$cshowList :: [ReadMemoryResponse] -> ShowS
showList :: [ReadMemoryResponse] -> ShowS
Show, ReadMemoryResponse -> ReadMemoryResponse -> Bool
(ReadMemoryResponse -> ReadMemoryResponse -> Bool)
-> (ReadMemoryResponse -> ReadMemoryResponse -> Bool)
-> Eq ReadMemoryResponse
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ReadMemoryResponse -> ReadMemoryResponse -> Bool
== :: ReadMemoryResponse -> ReadMemoryResponse -> Bool
$c/= :: ReadMemoryResponse -> ReadMemoryResponse -> Bool
/= :: ReadMemoryResponse -> ReadMemoryResponse -> Bool
Eq, (forall x. ReadMemoryResponse -> Rep ReadMemoryResponse x)
-> (forall x. Rep ReadMemoryResponse x -> ReadMemoryResponse)
-> Generic ReadMemoryResponse
forall x. Rep ReadMemoryResponse x -> ReadMemoryResponse
forall x. ReadMemoryResponse -> Rep ReadMemoryResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ReadMemoryResponse -> Rep ReadMemoryResponse x
from :: forall x. ReadMemoryResponse -> Rep ReadMemoryResponse x
$cto :: forall x. Rep ReadMemoryResponse x -> ReadMemoryResponse
to :: forall x. Rep ReadMemoryResponse x -> ReadMemoryResponse
Generic)
instance ToJSON ReadMemoryResponse where
  toJSON :: ReadMemoryResponse -> Value
toJSON = ReadMemoryResponse -> Value
forall a.
(Generic a, GToJSON Zero (Rep a), Typeable a) =>
a -> Value
genericToJSONWithModifier
data WriteMemoryResponse
  = WriteMemoryResponse
  { WriteMemoryResponse -> Maybe Int
writeMemoryResponseOffset :: Maybe Int
    
    
    
    
    
  , WriteMemoryResponse -> Maybe Int
writeMemoryResponseBytesWritten :: Maybe Int
    
    
    
    
  } deriving stock (Int -> WriteMemoryResponse -> ShowS
[WriteMemoryResponse] -> ShowS
WriteMemoryResponse -> String
(Int -> WriteMemoryResponse -> ShowS)
-> (WriteMemoryResponse -> String)
-> ([WriteMemoryResponse] -> ShowS)
-> Show WriteMemoryResponse
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> WriteMemoryResponse -> ShowS
showsPrec :: Int -> WriteMemoryResponse -> ShowS
$cshow :: WriteMemoryResponse -> String
show :: WriteMemoryResponse -> String
$cshowList :: [WriteMemoryResponse] -> ShowS
showList :: [WriteMemoryResponse] -> ShowS
Show, WriteMemoryResponse -> WriteMemoryResponse -> Bool
(WriteMemoryResponse -> WriteMemoryResponse -> Bool)
-> (WriteMemoryResponse -> WriteMemoryResponse -> Bool)
-> Eq WriteMemoryResponse
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: WriteMemoryResponse -> WriteMemoryResponse -> Bool
== :: WriteMemoryResponse -> WriteMemoryResponse -> Bool
$c/= :: WriteMemoryResponse -> WriteMemoryResponse -> Bool
/= :: WriteMemoryResponse -> WriteMemoryResponse -> Bool
Eq, (forall x. WriteMemoryResponse -> Rep WriteMemoryResponse x)
-> (forall x. Rep WriteMemoryResponse x -> WriteMemoryResponse)
-> Generic WriteMemoryResponse
forall x. Rep WriteMemoryResponse x -> WriteMemoryResponse
forall x. WriteMemoryResponse -> Rep WriteMemoryResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. WriteMemoryResponse -> Rep WriteMemoryResponse x
from :: forall x. WriteMemoryResponse -> Rep WriteMemoryResponse x
$cto :: forall x. Rep WriteMemoryResponse x -> WriteMemoryResponse
to :: forall x. Rep WriteMemoryResponse x -> WriteMemoryResponse
Generic)
instance ToJSON WriteMemoryResponse where
  toJSON :: WriteMemoryResponse -> Value
toJSON = WriteMemoryResponse -> Value
forall a.
(Generic a, GToJSON Zero (Rep a), Typeable a) =>
a -> Value
genericToJSONWithModifier
data DisassembleResponse
  = DisassembleResponse
  { DisassembleResponse -> [DisassembledInstruction]
disassembleResponseInstructions :: [DisassembledInstruction]
    
    
    
  } deriving stock (Int -> DisassembleResponse -> ShowS
[DisassembleResponse] -> ShowS
DisassembleResponse -> String
(Int -> DisassembleResponse -> ShowS)
-> (DisassembleResponse -> String)
-> ([DisassembleResponse] -> ShowS)
-> Show DisassembleResponse
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> DisassembleResponse -> ShowS
showsPrec :: Int -> DisassembleResponse -> ShowS
$cshow :: DisassembleResponse -> String
show :: DisassembleResponse -> String
$cshowList :: [DisassembleResponse] -> ShowS
showList :: [DisassembleResponse] -> ShowS
Show, DisassembleResponse -> DisassembleResponse -> Bool
(DisassembleResponse -> DisassembleResponse -> Bool)
-> (DisassembleResponse -> DisassembleResponse -> Bool)
-> Eq DisassembleResponse
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DisassembleResponse -> DisassembleResponse -> Bool
== :: DisassembleResponse -> DisassembleResponse -> Bool
$c/= :: DisassembleResponse -> DisassembleResponse -> Bool
/= :: DisassembleResponse -> DisassembleResponse -> Bool
Eq, (forall x. DisassembleResponse -> Rep DisassembleResponse x)
-> (forall x. Rep DisassembleResponse x -> DisassembleResponse)
-> Generic DisassembleResponse
forall x. Rep DisassembleResponse x -> DisassembleResponse
forall x. DisassembleResponse -> Rep DisassembleResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. DisassembleResponse -> Rep DisassembleResponse x
from :: forall x. DisassembleResponse -> Rep DisassembleResponse x
$cto :: forall x. Rep DisassembleResponse x -> DisassembleResponse
to :: forall x. Rep DisassembleResponse x -> DisassembleResponse
Generic)
instance ToJSON DisassembleResponse where
  toJSON :: DisassembleResponse -> Value
toJSON = DisassembleResponse -> Value
forall a.
(Generic a, GToJSON Zero (Rep a), Typeable a) =>
a -> Value
genericToJSONWithModifier
data DisassembledInstruction
  = DisassembledInstruction
  { DisassembledInstruction -> Text
disassembledInstructionAddress :: Text
    
    
    
  , DisassembledInstruction -> Maybe Text
disassembledInstructionInstructionBytes :: Maybe Text
    
    
    
  , DisassembledInstruction -> Text
disassembledInstructionInstruction :: Text
    
    
    
    
  , DisassembledInstruction -> Maybe Text
disassembledInstructionSymbol :: Maybe Text
    
    
    
    
  , DisassembledInstruction -> Maybe Source
disassembledInstructionLocation :: Maybe Source
    
    
    
    
    
    
  , DisassembledInstruction -> Maybe Int
disassembledInstructionLine :: Maybe Int
    
    
    
    
  , DisassembledInstruction -> Maybe Int
disassembledInstructionColumn :: Maybe Int
    
    
    
  , DisassembledInstruction -> Maybe Int
disassembledInstructionEndLine :: Maybe Int
    
    
    
  , DisassembledInstruction -> Maybe Int
disassembledInstructionEndColumn :: Maybe Int
    
    
    
  } deriving stock (Int -> DisassembledInstruction -> ShowS
[DisassembledInstruction] -> ShowS
DisassembledInstruction -> String
(Int -> DisassembledInstruction -> ShowS)
-> (DisassembledInstruction -> String)
-> ([DisassembledInstruction] -> ShowS)
-> Show DisassembledInstruction
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> DisassembledInstruction -> ShowS
showsPrec :: Int -> DisassembledInstruction -> ShowS
$cshow :: DisassembledInstruction -> String
show :: DisassembledInstruction -> String
$cshowList :: [DisassembledInstruction] -> ShowS
showList :: [DisassembledInstruction] -> ShowS
Show, DisassembledInstruction -> DisassembledInstruction -> Bool
(DisassembledInstruction -> DisassembledInstruction -> Bool)
-> (DisassembledInstruction -> DisassembledInstruction -> Bool)
-> Eq DisassembledInstruction
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DisassembledInstruction -> DisassembledInstruction -> Bool
== :: DisassembledInstruction -> DisassembledInstruction -> Bool
$c/= :: DisassembledInstruction -> DisassembledInstruction -> Bool
/= :: DisassembledInstruction -> DisassembledInstruction -> Bool
Eq, (forall x.
 DisassembledInstruction -> Rep DisassembledInstruction x)
-> (forall x.
    Rep DisassembledInstruction x -> DisassembledInstruction)
-> Generic DisassembledInstruction
forall x. Rep DisassembledInstruction x -> DisassembledInstruction
forall x. DisassembledInstruction -> Rep DisassembledInstruction x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. DisassembledInstruction -> Rep DisassembledInstruction x
from :: forall x. DisassembledInstruction -> Rep DisassembledInstruction x
$cto :: forall x. Rep DisassembledInstruction x -> DisassembledInstruction
to :: forall x. Rep DisassembledInstruction x -> DisassembledInstruction
Generic)
defaultDisassembledInstruction :: DisassembledInstruction
defaultDisassembledInstruction :: DisassembledInstruction
defaultDisassembledInstruction
  = DisassembledInstruction
  { disassembledInstructionAddress :: Text
disassembledInstructionAddress = Text
forall a. Monoid a => a
mempty
  , disassembledInstructionInstructionBytes :: Maybe Text
disassembledInstructionInstructionBytes = Maybe Text
forall a. Maybe a
Nothing
  , disassembledInstructionInstruction :: Text
disassembledInstructionInstruction = Text
forall a. Monoid a => a
mempty
  , disassembledInstructionSymbol :: Maybe Text
disassembledInstructionSymbol = Maybe Text
forall a. Maybe a
Nothing
  , disassembledInstructionLocation :: Maybe Source
disassembledInstructionLocation = Maybe Source
forall a. Maybe a
Nothing
  , disassembledInstructionLine :: Maybe Int
disassembledInstructionLine = Maybe Int
forall a. Maybe a
Nothing
  , disassembledInstructionColumn :: Maybe Int
disassembledInstructionColumn = Maybe Int
forall a. Maybe a
Nothing
  , disassembledInstructionEndLine :: Maybe Int
disassembledInstructionEndLine = Maybe Int
forall a. Maybe a
Nothing
  , disassembledInstructionEndColumn :: Maybe Int
disassembledInstructionEndColumn = Maybe Int
forall a. Maybe a
Nothing
  }
instance ToJSON DisassembledInstruction where
  toJSON :: DisassembledInstruction -> Value
toJSON = DisassembledInstruction -> Value
forall a.
(Generic a, GToJSON Zero (Rep a), Typeable a) =>
a -> Value
genericToJSONWithModifier
data StoppedEventReason
  = StoppedEventReasonStep
  | StoppedEventReasonBreakpoint
  | StoppedEventReasonException
  | StoppedEventReasonPause
  | StoppedEventReasonEntry
  | StoppedEventReasonGoto
  | StoppedEventReasonFunctionBreakpoint
  | StoppedEventReasonDataBreakpoint
  | StoppedEventReasonInstructionBreakpoint
  deriving stock (Int -> StoppedEventReason -> ShowS
[StoppedEventReason] -> ShowS
StoppedEventReason -> String
(Int -> StoppedEventReason -> ShowS)
-> (StoppedEventReason -> String)
-> ([StoppedEventReason] -> ShowS)
-> Show StoppedEventReason
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> StoppedEventReason -> ShowS
showsPrec :: Int -> StoppedEventReason -> ShowS
$cshow :: StoppedEventReason -> String
show :: StoppedEventReason -> String
$cshowList :: [StoppedEventReason] -> ShowS
showList :: [StoppedEventReason] -> ShowS
Show, StoppedEventReason -> StoppedEventReason -> Bool
(StoppedEventReason -> StoppedEventReason -> Bool)
-> (StoppedEventReason -> StoppedEventReason -> Bool)
-> Eq StoppedEventReason
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: StoppedEventReason -> StoppedEventReason -> Bool
== :: StoppedEventReason -> StoppedEventReason -> Bool
$c/= :: StoppedEventReason -> StoppedEventReason -> Bool
/= :: StoppedEventReason -> StoppedEventReason -> Bool
Eq)
instance ToJSON StoppedEventReason where
  toJSON :: StoppedEventReason -> Value
toJSON StoppedEventReason
StoppedEventReasonStep                  = Value
"step"
  toJSON StoppedEventReason
StoppedEventReasonBreakpoint            = Value
"breakpoint"
  toJSON StoppedEventReason
StoppedEventReasonException             = Value
"exception"
  toJSON StoppedEventReason
StoppedEventReasonPause                 = Value
"pause"
  toJSON StoppedEventReason
StoppedEventReasonEntry                 = Value
"entry"
  toJSON StoppedEventReason
StoppedEventReasonGoto                  = Value
"goto"
  toJSON StoppedEventReason
StoppedEventReasonFunctionBreakpoint    = Value
"function breakpoint"
  toJSON StoppedEventReason
StoppedEventReasonDataBreakpoint        = Value
"data breakpoint"
  toJSON StoppedEventReason
StoppedEventReasonInstructionBreakpoint = Value
"instruction breakpoint"
data StoppedEvent
  = StoppedEvent
  { StoppedEvent -> StoppedEventReason
stoppedEventReason :: StoppedEventReason
    
    
    
    
    
    
    
  , StoppedEvent -> Maybe Text
stoppedEventDescription :: Maybe Text
    
    
    
    
  , StoppedEvent -> Maybe Int
stoppedEventThreadId :: Maybe Int
    
    
    
  , StoppedEvent -> Bool
stoppedEventPreserveFocusHint :: Bool
    
    
    
    
  , StoppedEvent -> Maybe Text
stoppedEventText :: Maybe Text
    
    
    
    
  , StoppedEvent -> Bool
stoppedEventAllThreadsStopped :: Bool
    
    
    
    
    
    
    
    
  , StoppedEvent -> [Int]
stoppedEventHitBreakpointIds :: [Int]
    
    
    
    
    
    
    
    
    
    
  } deriving stock (Int -> StoppedEvent -> ShowS
[StoppedEvent] -> ShowS
StoppedEvent -> String
(Int -> StoppedEvent -> ShowS)
-> (StoppedEvent -> String)
-> ([StoppedEvent] -> ShowS)
-> Show StoppedEvent
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> StoppedEvent -> ShowS
showsPrec :: Int -> StoppedEvent -> ShowS
$cshow :: StoppedEvent -> String
show :: StoppedEvent -> String
$cshowList :: [StoppedEvent] -> ShowS
showList :: [StoppedEvent] -> ShowS
Show, StoppedEvent -> StoppedEvent -> Bool
(StoppedEvent -> StoppedEvent -> Bool)
-> (StoppedEvent -> StoppedEvent -> Bool) -> Eq StoppedEvent
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: StoppedEvent -> StoppedEvent -> Bool
== :: StoppedEvent -> StoppedEvent -> Bool
$c/= :: StoppedEvent -> StoppedEvent -> Bool
/= :: StoppedEvent -> StoppedEvent -> Bool
Eq, (forall x. StoppedEvent -> Rep StoppedEvent x)
-> (forall x. Rep StoppedEvent x -> StoppedEvent)
-> Generic StoppedEvent
forall x. Rep StoppedEvent x -> StoppedEvent
forall x. StoppedEvent -> Rep StoppedEvent x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. StoppedEvent -> Rep StoppedEvent x
from :: forall x. StoppedEvent -> Rep StoppedEvent x
$cto :: forall x. Rep StoppedEvent x -> StoppedEvent
to :: forall x. Rep StoppedEvent x -> StoppedEvent
Generic)
instance ToJSON StoppedEvent where
  toJSON :: StoppedEvent -> Value
toJSON = StoppedEvent -> Value
forall a.
(Generic a, GToJSON Zero (Rep a), Typeable a) =>
a -> Value
genericToJSONWithModifier
data ContinuedEvent
  = ContinuedEvent
  { ContinuedEvent -> Int
continuedEventThreadId :: Int
    
    
    
  , ContinuedEvent -> Bool
continuedEventAllThreadsContinued :: Bool
    
    
    
    
  } deriving stock (Int -> ContinuedEvent -> ShowS
[ContinuedEvent] -> ShowS
ContinuedEvent -> String
(Int -> ContinuedEvent -> ShowS)
-> (ContinuedEvent -> String)
-> ([ContinuedEvent] -> ShowS)
-> Show ContinuedEvent
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ContinuedEvent -> ShowS
showsPrec :: Int -> ContinuedEvent -> ShowS
$cshow :: ContinuedEvent -> String
show :: ContinuedEvent -> String
$cshowList :: [ContinuedEvent] -> ShowS
showList :: [ContinuedEvent] -> ShowS
Show, ContinuedEvent -> ContinuedEvent -> Bool
(ContinuedEvent -> ContinuedEvent -> Bool)
-> (ContinuedEvent -> ContinuedEvent -> Bool) -> Eq ContinuedEvent
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ContinuedEvent -> ContinuedEvent -> Bool
== :: ContinuedEvent -> ContinuedEvent -> Bool
$c/= :: ContinuedEvent -> ContinuedEvent -> Bool
/= :: ContinuedEvent -> ContinuedEvent -> Bool
Eq, (forall x. ContinuedEvent -> Rep ContinuedEvent x)
-> (forall x. Rep ContinuedEvent x -> ContinuedEvent)
-> Generic ContinuedEvent
forall x. Rep ContinuedEvent x -> ContinuedEvent
forall x. ContinuedEvent -> Rep ContinuedEvent x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ContinuedEvent -> Rep ContinuedEvent x
from :: forall x. ContinuedEvent -> Rep ContinuedEvent x
$cto :: forall x. Rep ContinuedEvent x -> ContinuedEvent
to :: forall x. Rep ContinuedEvent x -> ContinuedEvent
Generic)
instance ToJSON ContinuedEvent where
  toJSON :: ContinuedEvent -> Value
toJSON = ContinuedEvent -> Value
forall a.
(Generic a, GToJSON Zero (Rep a), Typeable a) =>
a -> Value
genericToJSONWithModifier
data ExitedEvent
  = ExitedEvent
  { ExitedEvent -> Int
exitedEventExitCode :: Int
    
    
    
  } deriving stock (Int -> ExitedEvent -> ShowS
[ExitedEvent] -> ShowS
ExitedEvent -> String
(Int -> ExitedEvent -> ShowS)
-> (ExitedEvent -> String)
-> ([ExitedEvent] -> ShowS)
-> Show ExitedEvent
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ExitedEvent -> ShowS
showsPrec :: Int -> ExitedEvent -> ShowS
$cshow :: ExitedEvent -> String
show :: ExitedEvent -> String
$cshowList :: [ExitedEvent] -> ShowS
showList :: [ExitedEvent] -> ShowS
Show, ExitedEvent -> ExitedEvent -> Bool
(ExitedEvent -> ExitedEvent -> Bool)
-> (ExitedEvent -> ExitedEvent -> Bool) -> Eq ExitedEvent
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ExitedEvent -> ExitedEvent -> Bool
== :: ExitedEvent -> ExitedEvent -> Bool
$c/= :: ExitedEvent -> ExitedEvent -> Bool
/= :: ExitedEvent -> ExitedEvent -> Bool
Eq, (forall x. ExitedEvent -> Rep ExitedEvent x)
-> (forall x. Rep ExitedEvent x -> ExitedEvent)
-> Generic ExitedEvent
forall x. Rep ExitedEvent x -> ExitedEvent
forall x. ExitedEvent -> Rep ExitedEvent x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ExitedEvent -> Rep ExitedEvent x
from :: forall x. ExitedEvent -> Rep ExitedEvent x
$cto :: forall x. Rep ExitedEvent x -> ExitedEvent
to :: forall x. Rep ExitedEvent x -> ExitedEvent
Generic)
instance ToJSON ExitedEvent where
  toJSON :: ExitedEvent -> Value
toJSON = ExitedEvent -> Value
forall a.
(Generic a, GToJSON Zero (Rep a), Typeable a) =>
a -> Value
genericToJSONWithModifier
data TerminatedEvent
  = TerminatedEvent
  { TerminatedEvent -> Bool
terminatedEventRestart :: Bool
    
    
    
    
    
    
  } deriving stock (Int -> TerminatedEvent -> ShowS
[TerminatedEvent] -> ShowS
TerminatedEvent -> String
(Int -> TerminatedEvent -> ShowS)
-> (TerminatedEvent -> String)
-> ([TerminatedEvent] -> ShowS)
-> Show TerminatedEvent
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TerminatedEvent -> ShowS
showsPrec :: Int -> TerminatedEvent -> ShowS
$cshow :: TerminatedEvent -> String
show :: TerminatedEvent -> String
$cshowList :: [TerminatedEvent] -> ShowS
showList :: [TerminatedEvent] -> ShowS
Show, TerminatedEvent -> TerminatedEvent -> Bool
(TerminatedEvent -> TerminatedEvent -> Bool)
-> (TerminatedEvent -> TerminatedEvent -> Bool)
-> Eq TerminatedEvent
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TerminatedEvent -> TerminatedEvent -> Bool
== :: TerminatedEvent -> TerminatedEvent -> Bool
$c/= :: TerminatedEvent -> TerminatedEvent -> Bool
/= :: TerminatedEvent -> TerminatedEvent -> Bool
Eq, (forall x. TerminatedEvent -> Rep TerminatedEvent x)
-> (forall x. Rep TerminatedEvent x -> TerminatedEvent)
-> Generic TerminatedEvent
forall x. Rep TerminatedEvent x -> TerminatedEvent
forall x. TerminatedEvent -> Rep TerminatedEvent x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. TerminatedEvent -> Rep TerminatedEvent x
from :: forall x. TerminatedEvent -> Rep TerminatedEvent x
$cto :: forall x. Rep TerminatedEvent x -> TerminatedEvent
to :: forall x. Rep TerminatedEvent x -> TerminatedEvent
Generic)
instance ToJSON TerminatedEvent where
  toJSON :: TerminatedEvent -> Value
toJSON = TerminatedEvent -> Value
forall a.
(Generic a, GToJSON Zero (Rep a), Typeable a) =>
a -> Value
genericToJSONWithModifier
data ThreadEvent
  = ThreadEvent
  { ThreadEvent -> ThreadEventReason
threadEventReason :: ThreadEventReason
    
    
    
    
  , ThreadEvent -> Int
threadEventThreadId :: Int
    
    
    
  } deriving stock (Int -> ThreadEvent -> ShowS
[ThreadEvent] -> ShowS
ThreadEvent -> String
(Int -> ThreadEvent -> ShowS)
-> (ThreadEvent -> String)
-> ([ThreadEvent] -> ShowS)
-> Show ThreadEvent
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ThreadEvent -> ShowS
showsPrec :: Int -> ThreadEvent -> ShowS
$cshow :: ThreadEvent -> String
show :: ThreadEvent -> String
$cshowList :: [ThreadEvent] -> ShowS
showList :: [ThreadEvent] -> ShowS
Show, ThreadEvent -> ThreadEvent -> Bool
(ThreadEvent -> ThreadEvent -> Bool)
-> (ThreadEvent -> ThreadEvent -> Bool) -> Eq ThreadEvent
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ThreadEvent -> ThreadEvent -> Bool
== :: ThreadEvent -> ThreadEvent -> Bool
$c/= :: ThreadEvent -> ThreadEvent -> Bool
/= :: ThreadEvent -> ThreadEvent -> Bool
Eq, (forall x. ThreadEvent -> Rep ThreadEvent x)
-> (forall x. Rep ThreadEvent x -> ThreadEvent)
-> Generic ThreadEvent
forall x. Rep ThreadEvent x -> ThreadEvent
forall x. ThreadEvent -> Rep ThreadEvent x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ThreadEvent -> Rep ThreadEvent x
from :: forall x. ThreadEvent -> Rep ThreadEvent x
$cto :: forall x. Rep ThreadEvent x -> ThreadEvent
to :: forall x. Rep ThreadEvent x -> ThreadEvent
Generic)
instance ToJSON ThreadEvent where
  toJSON :: ThreadEvent -> Value
toJSON = ThreadEvent -> Value
forall a.
(Generic a, GToJSON Zero (Rep a), Typeable a) =>
a -> Value
genericToJSONWithModifier
data ThreadEventReason
  = ThreadEventReasonStarted
  | ThreadEventReasonExited
  | ThreadEventReason Text
  deriving stock (Int -> ThreadEventReason -> ShowS
[ThreadEventReason] -> ShowS
ThreadEventReason -> String
(Int -> ThreadEventReason -> ShowS)
-> (ThreadEventReason -> String)
-> ([ThreadEventReason] -> ShowS)
-> Show ThreadEventReason
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ThreadEventReason -> ShowS
showsPrec :: Int -> ThreadEventReason -> ShowS
$cshow :: ThreadEventReason -> String
show :: ThreadEventReason -> String
$cshowList :: [ThreadEventReason] -> ShowS
showList :: [ThreadEventReason] -> ShowS
Show, ThreadEventReason -> ThreadEventReason -> Bool
(ThreadEventReason -> ThreadEventReason -> Bool)
-> (ThreadEventReason -> ThreadEventReason -> Bool)
-> Eq ThreadEventReason
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ThreadEventReason -> ThreadEventReason -> Bool
== :: ThreadEventReason -> ThreadEventReason -> Bool
$c/= :: ThreadEventReason -> ThreadEventReason -> Bool
/= :: ThreadEventReason -> ThreadEventReason -> Bool
Eq, (forall x. ThreadEventReason -> Rep ThreadEventReason x)
-> (forall x. Rep ThreadEventReason x -> ThreadEventReason)
-> Generic ThreadEventReason
forall x. Rep ThreadEventReason x -> ThreadEventReason
forall x. ThreadEventReason -> Rep ThreadEventReason x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ThreadEventReason -> Rep ThreadEventReason x
from :: forall x. ThreadEventReason -> Rep ThreadEventReason x
$cto :: forall x. Rep ThreadEventReason x -> ThreadEventReason
to :: forall x. Rep ThreadEventReason x -> ThreadEventReason
Generic)
instance ToJSON ThreadEventReason where
  toJSON :: ThreadEventReason -> Value
toJSON (ThreadEventReason Text
reason)       = Text -> Value
forall a. ToJSON a => a -> Value
toJSON Text
reason
  toJSON ThreadEventReason
reason = ThreadEventReason -> Value
forall a.
(Generic a, GToJSON Zero (Rep a), Typeable a) =>
a -> Value
genericToJSONWithModifier ThreadEventReason
reason
data OutputEventCategory
  = OutputEventCategoryConsole
  | OutputEventCategoryImportant
  | OutputEventCategoryStdout
  | OutputEventCategoryStderr
  | OutputEventCategoryTelemetry
  | OutputEventCategory Text
  deriving stock (Int -> OutputEventCategory -> ShowS
[OutputEventCategory] -> ShowS
OutputEventCategory -> String
(Int -> OutputEventCategory -> ShowS)
-> (OutputEventCategory -> String)
-> ([OutputEventCategory] -> ShowS)
-> Show OutputEventCategory
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> OutputEventCategory -> ShowS
showsPrec :: Int -> OutputEventCategory -> ShowS
$cshow :: OutputEventCategory -> String
show :: OutputEventCategory -> String
$cshowList :: [OutputEventCategory] -> ShowS
showList :: [OutputEventCategory] -> ShowS
Show, OutputEventCategory -> OutputEventCategory -> Bool
(OutputEventCategory -> OutputEventCategory -> Bool)
-> (OutputEventCategory -> OutputEventCategory -> Bool)
-> Eq OutputEventCategory
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: OutputEventCategory -> OutputEventCategory -> Bool
== :: OutputEventCategory -> OutputEventCategory -> Bool
$c/= :: OutputEventCategory -> OutputEventCategory -> Bool
/= :: OutputEventCategory -> OutputEventCategory -> Bool
Eq, (forall x. OutputEventCategory -> Rep OutputEventCategory x)
-> (forall x. Rep OutputEventCategory x -> OutputEventCategory)
-> Generic OutputEventCategory
forall x. Rep OutputEventCategory x -> OutputEventCategory
forall x. OutputEventCategory -> Rep OutputEventCategory x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. OutputEventCategory -> Rep OutputEventCategory x
from :: forall x. OutputEventCategory -> Rep OutputEventCategory x
$cto :: forall x. Rep OutputEventCategory x -> OutputEventCategory
to :: forall x. Rep OutputEventCategory x -> OutputEventCategory
Generic)
instance ToJSON OutputEventCategory where
  toJSON :: OutputEventCategory -> Value
toJSON (OutputEventCategory Text
category) = Text -> Value
forall a. ToJSON a => a -> Value
toJSON Text
category
  toJSON OutputEventCategory
category = OutputEventCategory -> Value
forall a.
(Generic a, GToJSON Zero (Rep a), Typeable a) =>
a -> Value
genericToJSONWithModifier OutputEventCategory
category
data EventGroup
  = EventGroupStart
  | EventGroupStartCollapsed
  | EventGroupEnd
  deriving stock (Int -> EventGroup -> ShowS
[EventGroup] -> ShowS
EventGroup -> String
(Int -> EventGroup -> ShowS)
-> (EventGroup -> String)
-> ([EventGroup] -> ShowS)
-> Show EventGroup
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> EventGroup -> ShowS
showsPrec :: Int -> EventGroup -> ShowS
$cshow :: EventGroup -> String
show :: EventGroup -> String
$cshowList :: [EventGroup] -> ShowS
showList :: [EventGroup] -> ShowS
Show, EventGroup -> EventGroup -> Bool
(EventGroup -> EventGroup -> Bool)
-> (EventGroup -> EventGroup -> Bool) -> Eq EventGroup
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: EventGroup -> EventGroup -> Bool
== :: EventGroup -> EventGroup -> Bool
$c/= :: EventGroup -> EventGroup -> Bool
/= :: EventGroup -> EventGroup -> Bool
Eq, (forall x. EventGroup -> Rep EventGroup x)
-> (forall x. Rep EventGroup x -> EventGroup) -> Generic EventGroup
forall x. Rep EventGroup x -> EventGroup
forall x. EventGroup -> Rep EventGroup x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. EventGroup -> Rep EventGroup x
from :: forall x. EventGroup -> Rep EventGroup x
$cto :: forall x. Rep EventGroup x -> EventGroup
to :: forall x. Rep EventGroup x -> EventGroup
Generic)
instance ToJSON EventGroup where
  toJSON :: EventGroup -> Value
toJSON = EventGroup -> Value
forall a.
(Generic a, GToJSON Zero (Rep a), Typeable a) =>
a -> Value
genericToJSONWithModifier
data OutputEvent
  = OutputEvent
  { OutputEvent -> Maybe OutputEventCategory
outputEventCategory :: Maybe OutputEventCategory
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
  , OutputEvent -> Text
outputEventOutput :: Text
    
    
    
  , OutputEvent -> Maybe EventGroup
outputEventGroup :: Maybe EventGroup
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
  , OutputEvent -> Maybe Int
outputEventVariablesReference :: Maybe Int
    
    
    
    
    
    
    
  , OutputEvent -> Maybe Source
outputEventSource :: Maybe Source
    
    
    
  , OutputEvent -> Maybe Int
outputEventLine :: Maybe Int
    
    
    
  , OutputEvent -> Maybe Int
outputEventColumn :: Maybe Int
    
    
    
    
    
  , OutputEvent -> Maybe Value
outputEventData :: Maybe Value
    
    
    
    
  } deriving stock (Int -> OutputEvent -> ShowS
[OutputEvent] -> ShowS
OutputEvent -> String
(Int -> OutputEvent -> ShowS)
-> (OutputEvent -> String)
-> ([OutputEvent] -> ShowS)
-> Show OutputEvent
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> OutputEvent -> ShowS
showsPrec :: Int -> OutputEvent -> ShowS
$cshow :: OutputEvent -> String
show :: OutputEvent -> String
$cshowList :: [OutputEvent] -> ShowS
showList :: [OutputEvent] -> ShowS
Show, OutputEvent -> OutputEvent -> Bool
(OutputEvent -> OutputEvent -> Bool)
-> (OutputEvent -> OutputEvent -> Bool) -> Eq OutputEvent
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: OutputEvent -> OutputEvent -> Bool
== :: OutputEvent -> OutputEvent -> Bool
$c/= :: OutputEvent -> OutputEvent -> Bool
/= :: OutputEvent -> OutputEvent -> Bool
Eq, (forall x. OutputEvent -> Rep OutputEvent x)
-> (forall x. Rep OutputEvent x -> OutputEvent)
-> Generic OutputEvent
forall x. Rep OutputEvent x -> OutputEvent
forall x. OutputEvent -> Rep OutputEvent x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. OutputEvent -> Rep OutputEvent x
from :: forall x. OutputEvent -> Rep OutputEvent x
$cto :: forall x. Rep OutputEvent x -> OutputEvent
to :: forall x. Rep OutputEvent x -> OutputEvent
Generic)
instance ToJSON OutputEvent where
  toJSON :: OutputEvent -> Value
toJSON = OutputEvent -> Value
forall a.
(Generic a, GToJSON Zero (Rep a), Typeable a) =>
a -> Value
genericToJSONWithModifier
data BreakpointEvent
  = BreakpointEvent
  { BreakpointEvent -> EventReason
breakpointEventReason :: EventReason
    
    
    
    
  , BreakpointEvent -> Breakpoint
breakpointEvevntBreakpoint :: Breakpoint
    
    
    
    
  } deriving stock (Int -> BreakpointEvent -> ShowS
[BreakpointEvent] -> ShowS
BreakpointEvent -> String
(Int -> BreakpointEvent -> ShowS)
-> (BreakpointEvent -> String)
-> ([BreakpointEvent] -> ShowS)
-> Show BreakpointEvent
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> BreakpointEvent -> ShowS
showsPrec :: Int -> BreakpointEvent -> ShowS
$cshow :: BreakpointEvent -> String
show :: BreakpointEvent -> String
$cshowList :: [BreakpointEvent] -> ShowS
showList :: [BreakpointEvent] -> ShowS
Show, BreakpointEvent -> BreakpointEvent -> Bool
(BreakpointEvent -> BreakpointEvent -> Bool)
-> (BreakpointEvent -> BreakpointEvent -> Bool)
-> Eq BreakpointEvent
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: BreakpointEvent -> BreakpointEvent -> Bool
== :: BreakpointEvent -> BreakpointEvent -> Bool
$c/= :: BreakpointEvent -> BreakpointEvent -> Bool
/= :: BreakpointEvent -> BreakpointEvent -> Bool
Eq, (forall x. BreakpointEvent -> Rep BreakpointEvent x)
-> (forall x. Rep BreakpointEvent x -> BreakpointEvent)
-> Generic BreakpointEvent
forall x. Rep BreakpointEvent x -> BreakpointEvent
forall x. BreakpointEvent -> Rep BreakpointEvent x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. BreakpointEvent -> Rep BreakpointEvent x
from :: forall x. BreakpointEvent -> Rep BreakpointEvent x
$cto :: forall x. Rep BreakpointEvent x -> BreakpointEvent
to :: forall x. Rep BreakpointEvent x -> BreakpointEvent
Generic)
instance ToJSON BreakpointEvent where
  toJSON :: BreakpointEvent -> Value
toJSON = BreakpointEvent -> Value
forall a.
(Generic a, GToJSON Zero (Rep a), Typeable a) =>
a -> Value
genericToJSONWithModifier
data EventReason
  = EventReasonNew
  | EventReasonChanged
  | EventReasonRemoved
  | EventReason Text
  deriving stock (Int -> EventReason -> ShowS
[EventReason] -> ShowS
EventReason -> String
(Int -> EventReason -> ShowS)
-> (EventReason -> String)
-> ([EventReason] -> ShowS)
-> Show EventReason
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> EventReason -> ShowS
showsPrec :: Int -> EventReason -> ShowS
$cshow :: EventReason -> String
show :: EventReason -> String
$cshowList :: [EventReason] -> ShowS
showList :: [EventReason] -> ShowS
Show, EventReason -> EventReason -> Bool
(EventReason -> EventReason -> Bool)
-> (EventReason -> EventReason -> Bool) -> Eq EventReason
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: EventReason -> EventReason -> Bool
== :: EventReason -> EventReason -> Bool
$c/= :: EventReason -> EventReason -> Bool
/= :: EventReason -> EventReason -> Bool
Eq, (forall x. EventReason -> Rep EventReason x)
-> (forall x. Rep EventReason x -> EventReason)
-> Generic EventReason
forall x. Rep EventReason x -> EventReason
forall x. EventReason -> Rep EventReason x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. EventReason -> Rep EventReason x
from :: forall x. EventReason -> Rep EventReason x
$cto :: forall x. Rep EventReason x -> EventReason
to :: forall x. Rep EventReason x -> EventReason
Generic)
instance ToJSON EventReason where
  toJSON :: EventReason -> Value
toJSON (EventReason Text
reason) = Text -> Value
forall a. ToJSON a => a -> Value
toJSON Text
reason
  toJSON EventReason
reason = EventReason -> Value
forall a.
(Generic a, GToJSON Zero (Rep a), Typeable a) =>
a -> Value
genericToJSONWithModifier EventReason
reason
data ModuleEvent
  = ModuleEvent
  { ModuleEvent -> EventReason
moduleEventReason :: EventReason
    
    
    
    
  , ModuleEvent -> Module
moduleEventModule :: Module
    
    
    
    
  } deriving stock (Int -> ModuleEvent -> ShowS
[ModuleEvent] -> ShowS
ModuleEvent -> String
(Int -> ModuleEvent -> ShowS)
-> (ModuleEvent -> String)
-> ([ModuleEvent] -> ShowS)
-> Show ModuleEvent
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ModuleEvent -> ShowS
showsPrec :: Int -> ModuleEvent -> ShowS
$cshow :: ModuleEvent -> String
show :: ModuleEvent -> String
$cshowList :: [ModuleEvent] -> ShowS
showList :: [ModuleEvent] -> ShowS
Show, ModuleEvent -> ModuleEvent -> Bool
(ModuleEvent -> ModuleEvent -> Bool)
-> (ModuleEvent -> ModuleEvent -> Bool) -> Eq ModuleEvent
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ModuleEvent -> ModuleEvent -> Bool
== :: ModuleEvent -> ModuleEvent -> Bool
$c/= :: ModuleEvent -> ModuleEvent -> Bool
/= :: ModuleEvent -> ModuleEvent -> Bool
Eq)
instance ToJSON ModuleEvent where
  toJSON :: ModuleEvent -> Value
toJSON ModuleEvent{EventReason
Module
moduleEventReason :: ModuleEvent -> EventReason
moduleEventModule :: ModuleEvent -> Module
moduleEventReason :: EventReason
moduleEventModule :: Module
..} =
    [Pair] -> Value
object
      [ Key
"reason" Key -> EventReason -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= EventReason
moduleEventReason
      , Key
"module" Key -> Module -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Module
moduleEventModule
      ]
data LoadedSourceEvent
  = LoadedSourceEvent
  { LoadedSourceEvent -> EventReason
loadedSourceEventReason :: EventReason
    
    
    
    
  , LoadedSourceEvent -> Source
loadedSourceSource :: Source
    
    
    
  } deriving stock (Int -> LoadedSourceEvent -> ShowS
[LoadedSourceEvent] -> ShowS
LoadedSourceEvent -> String
(Int -> LoadedSourceEvent -> ShowS)
-> (LoadedSourceEvent -> String)
-> ([LoadedSourceEvent] -> ShowS)
-> Show LoadedSourceEvent
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> LoadedSourceEvent -> ShowS
showsPrec :: Int -> LoadedSourceEvent -> ShowS
$cshow :: LoadedSourceEvent -> String
show :: LoadedSourceEvent -> String
$cshowList :: [LoadedSourceEvent] -> ShowS
showList :: [LoadedSourceEvent] -> ShowS
Show, LoadedSourceEvent -> LoadedSourceEvent -> Bool
(LoadedSourceEvent -> LoadedSourceEvent -> Bool)
-> (LoadedSourceEvent -> LoadedSourceEvent -> Bool)
-> Eq LoadedSourceEvent
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: LoadedSourceEvent -> LoadedSourceEvent -> Bool
== :: LoadedSourceEvent -> LoadedSourceEvent -> Bool
$c/= :: LoadedSourceEvent -> LoadedSourceEvent -> Bool
/= :: LoadedSourceEvent -> LoadedSourceEvent -> Bool
Eq)
instance ToJSON LoadedSourceEvent where
  toJSON :: LoadedSourceEvent -> Value
toJSON LoadedSourceEvent{EventReason
Source
loadedSourceEventReason :: LoadedSourceEvent -> EventReason
loadedSourceSource :: LoadedSourceEvent -> Source
loadedSourceEventReason :: EventReason
loadedSourceSource :: Source
..}
    = [Pair] -> Value
object
    [ Key
"reason" Key -> EventReason -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= EventReason
loadedSourceEventReason
    , Key
"source" Key -> Source -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Source
loadedSourceSource
    ]
data ProcessEvent
  = ProcessEvent
  { ProcessEvent -> Text
processEventName :: Text
    
    
    
    
  , ProcessEvent -> Maybe Int
processEventSystemProcessId :: Maybe Int
    
    
    
    
  , ProcessEvent -> Bool
processEventIsLocalProcess :: Bool
    
    
    
    
  , ProcessEvent -> Maybe StartMethod
processEventStartMethod :: Maybe StartMethod
    
    
    
    
    
    
    
    
  , ProcessEvent -> Maybe Int
processEventPointerSize :: Maybe Int
    
    
    
    
  } deriving stock (Int -> ProcessEvent -> ShowS
[ProcessEvent] -> ShowS
ProcessEvent -> String
(Int -> ProcessEvent -> ShowS)
-> (ProcessEvent -> String)
-> ([ProcessEvent] -> ShowS)
-> Show ProcessEvent
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ProcessEvent -> ShowS
showsPrec :: Int -> ProcessEvent -> ShowS
$cshow :: ProcessEvent -> String
show :: ProcessEvent -> String
$cshowList :: [ProcessEvent] -> ShowS
showList :: [ProcessEvent] -> ShowS
Show, ProcessEvent -> ProcessEvent -> Bool
(ProcessEvent -> ProcessEvent -> Bool)
-> (ProcessEvent -> ProcessEvent -> Bool) -> Eq ProcessEvent
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ProcessEvent -> ProcessEvent -> Bool
== :: ProcessEvent -> ProcessEvent -> Bool
$c/= :: ProcessEvent -> ProcessEvent -> Bool
/= :: ProcessEvent -> ProcessEvent -> Bool
Eq, (forall x. ProcessEvent -> Rep ProcessEvent x)
-> (forall x. Rep ProcessEvent x -> ProcessEvent)
-> Generic ProcessEvent
forall x. Rep ProcessEvent x -> ProcessEvent
forall x. ProcessEvent -> Rep ProcessEvent x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ProcessEvent -> Rep ProcessEvent x
from :: forall x. ProcessEvent -> Rep ProcessEvent x
$cto :: forall x. Rep ProcessEvent x -> ProcessEvent
to :: forall x. Rep ProcessEvent x -> ProcessEvent
Generic)
instance ToJSON ProcessEvent where
  toJSON :: ProcessEvent -> Value
toJSON = ProcessEvent -> Value
forall a.
(Generic a, GToJSON Zero (Rep a), Typeable a) =>
a -> Value
genericToJSONWithModifier
data StartMethod
  = StartMethodLaunch
  | StartMethodAttach
  | StartMethodAttachForSuspendedLaunch
   deriving stock (Int -> StartMethod -> ShowS
[StartMethod] -> ShowS
StartMethod -> String
(Int -> StartMethod -> ShowS)
-> (StartMethod -> String)
-> ([StartMethod] -> ShowS)
-> Show StartMethod
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> StartMethod -> ShowS
showsPrec :: Int -> StartMethod -> ShowS
$cshow :: StartMethod -> String
show :: StartMethod -> String
$cshowList :: [StartMethod] -> ShowS
showList :: [StartMethod] -> ShowS
Show, StartMethod -> StartMethod -> Bool
(StartMethod -> StartMethod -> Bool)
-> (StartMethod -> StartMethod -> Bool) -> Eq StartMethod
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: StartMethod -> StartMethod -> Bool
== :: StartMethod -> StartMethod -> Bool
$c/= :: StartMethod -> StartMethod -> Bool
/= :: StartMethod -> StartMethod -> Bool
Eq, (forall x. StartMethod -> Rep StartMethod x)
-> (forall x. Rep StartMethod x -> StartMethod)
-> Generic StartMethod
forall x. Rep StartMethod x -> StartMethod
forall x. StartMethod -> Rep StartMethod x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. StartMethod -> Rep StartMethod x
from :: forall x. StartMethod -> Rep StartMethod x
$cto :: forall x. Rep StartMethod x -> StartMethod
to :: forall x. Rep StartMethod x -> StartMethod
Generic)
instance ToJSON StartMethod where
  toJSON :: StartMethod -> Value
toJSON = StartMethod -> Value
forall a.
(Generic a, GToJSON Zero (Rep a), Typeable a) =>
a -> Value
genericToJSONWithModifier
data CapabilitiesEvent
  = CapabilitiesEvent
  { CapabilitiesEvent -> Capabilities
capabilities :: Capabilities
    
    
    
  } deriving stock (Int -> CapabilitiesEvent -> ShowS
[CapabilitiesEvent] -> ShowS
CapabilitiesEvent -> String
(Int -> CapabilitiesEvent -> ShowS)
-> (CapabilitiesEvent -> String)
-> ([CapabilitiesEvent] -> ShowS)
-> Show CapabilitiesEvent
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CapabilitiesEvent -> ShowS
showsPrec :: Int -> CapabilitiesEvent -> ShowS
$cshow :: CapabilitiesEvent -> String
show :: CapabilitiesEvent -> String
$cshowList :: [CapabilitiesEvent] -> ShowS
showList :: [CapabilitiesEvent] -> ShowS
Show, CapabilitiesEvent -> CapabilitiesEvent -> Bool
(CapabilitiesEvent -> CapabilitiesEvent -> Bool)
-> (CapabilitiesEvent -> CapabilitiesEvent -> Bool)
-> Eq CapabilitiesEvent
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CapabilitiesEvent -> CapabilitiesEvent -> Bool
== :: CapabilitiesEvent -> CapabilitiesEvent -> Bool
$c/= :: CapabilitiesEvent -> CapabilitiesEvent -> Bool
/= :: CapabilitiesEvent -> CapabilitiesEvent -> Bool
Eq, (forall x. CapabilitiesEvent -> Rep CapabilitiesEvent x)
-> (forall x. Rep CapabilitiesEvent x -> CapabilitiesEvent)
-> Generic CapabilitiesEvent
forall x. Rep CapabilitiesEvent x -> CapabilitiesEvent
forall x. CapabilitiesEvent -> Rep CapabilitiesEvent x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. CapabilitiesEvent -> Rep CapabilitiesEvent x
from :: forall x. CapabilitiesEvent -> Rep CapabilitiesEvent x
$cto :: forall x. Rep CapabilitiesEvent x -> CapabilitiesEvent
to :: forall x. Rep CapabilitiesEvent x -> CapabilitiesEvent
Generic)
instance ToJSON CapabilitiesEvent where
  toJSON :: CapabilitiesEvent -> Value
toJSON = CapabilitiesEvent -> Value
forall a.
(Generic a, GToJSON Zero (Rep a), Typeable a) =>
a -> Value
genericToJSONWithModifier
data ProgressStartEvent
  = ProgressStartEvent
  { ProgressStartEvent -> Text
progressStartEventProgressId :: Text
    
    
    
    
    
  , ProgressStartEvent -> Text
progressStartEventTitle :: Text
    
    
    
    
  , ProgressStartEvent -> Maybe Int
progressStartEventRequestId :: Maybe Int
    
    
    
    
    
    
    
  , ProgressStartEvent -> Bool
progressStartEventCancellable :: Bool
    
    
    
    
    
    
    
    
  , ProgressStartEvent -> Maybe Text
progressStartEventMessage :: Maybe Text
    
    
    
  , ProgressStartEvent -> Maybe Int
progressStartEventPercentage :: Maybe Int
    
    
    
    
  } deriving stock (Int -> ProgressStartEvent -> ShowS
[ProgressStartEvent] -> ShowS
ProgressStartEvent -> String
(Int -> ProgressStartEvent -> ShowS)
-> (ProgressStartEvent -> String)
-> ([ProgressStartEvent] -> ShowS)
-> Show ProgressStartEvent
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ProgressStartEvent -> ShowS
showsPrec :: Int -> ProgressStartEvent -> ShowS
$cshow :: ProgressStartEvent -> String
show :: ProgressStartEvent -> String
$cshowList :: [ProgressStartEvent] -> ShowS
showList :: [ProgressStartEvent] -> ShowS
Show, ProgressStartEvent -> ProgressStartEvent -> Bool
(ProgressStartEvent -> ProgressStartEvent -> Bool)
-> (ProgressStartEvent -> ProgressStartEvent -> Bool)
-> Eq ProgressStartEvent
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ProgressStartEvent -> ProgressStartEvent -> Bool
== :: ProgressStartEvent -> ProgressStartEvent -> Bool
$c/= :: ProgressStartEvent -> ProgressStartEvent -> Bool
/= :: ProgressStartEvent -> ProgressStartEvent -> Bool
Eq, (forall x. ProgressStartEvent -> Rep ProgressStartEvent x)
-> (forall x. Rep ProgressStartEvent x -> ProgressStartEvent)
-> Generic ProgressStartEvent
forall x. Rep ProgressStartEvent x -> ProgressStartEvent
forall x. ProgressStartEvent -> Rep ProgressStartEvent x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ProgressStartEvent -> Rep ProgressStartEvent x
from :: forall x. ProgressStartEvent -> Rep ProgressStartEvent x
$cto :: forall x. Rep ProgressStartEvent x -> ProgressStartEvent
to :: forall x. Rep ProgressStartEvent x -> ProgressStartEvent
Generic)
instance ToJSON ProgressStartEvent where
  toJSON :: ProgressStartEvent -> Value
toJSON = ProgressStartEvent -> Value
forall a.
(Generic a, GToJSON Zero (Rep a), Typeable a) =>
a -> Value
genericToJSONWithModifier
data ProgressUpdateEvent
  = ProgressUpdateEvent
  { ProgressUpdateEvent -> Text
progressUpdateEventProgressId :: Text
    
    
    
  , ProgressUpdateEvent -> Maybe Text
progressUpdateEventMessage :: Maybe Text
    
    
    
    
  , ProgressUpdateEvent -> Maybe Int
progressUpdateEventPercentage :: Maybe Int
    
    
    
    
  } deriving stock (Int -> ProgressUpdateEvent -> ShowS
[ProgressUpdateEvent] -> ShowS
ProgressUpdateEvent -> String
(Int -> ProgressUpdateEvent -> ShowS)
-> (ProgressUpdateEvent -> String)
-> ([ProgressUpdateEvent] -> ShowS)
-> Show ProgressUpdateEvent
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ProgressUpdateEvent -> ShowS
showsPrec :: Int -> ProgressUpdateEvent -> ShowS
$cshow :: ProgressUpdateEvent -> String
show :: ProgressUpdateEvent -> String
$cshowList :: [ProgressUpdateEvent] -> ShowS
showList :: [ProgressUpdateEvent] -> ShowS
Show, ProgressUpdateEvent -> ProgressUpdateEvent -> Bool
(ProgressUpdateEvent -> ProgressUpdateEvent -> Bool)
-> (ProgressUpdateEvent -> ProgressUpdateEvent -> Bool)
-> Eq ProgressUpdateEvent
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ProgressUpdateEvent -> ProgressUpdateEvent -> Bool
== :: ProgressUpdateEvent -> ProgressUpdateEvent -> Bool
$c/= :: ProgressUpdateEvent -> ProgressUpdateEvent -> Bool
/= :: ProgressUpdateEvent -> ProgressUpdateEvent -> Bool
Eq, (forall x. ProgressUpdateEvent -> Rep ProgressUpdateEvent x)
-> (forall x. Rep ProgressUpdateEvent x -> ProgressUpdateEvent)
-> Generic ProgressUpdateEvent
forall x. Rep ProgressUpdateEvent x -> ProgressUpdateEvent
forall x. ProgressUpdateEvent -> Rep ProgressUpdateEvent x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ProgressUpdateEvent -> Rep ProgressUpdateEvent x
from :: forall x. ProgressUpdateEvent -> Rep ProgressUpdateEvent x
$cto :: forall x. Rep ProgressUpdateEvent x -> ProgressUpdateEvent
to :: forall x. Rep ProgressUpdateEvent x -> ProgressUpdateEvent
Generic)
instance ToJSON ProgressUpdateEvent where
  toJSON :: ProgressUpdateEvent -> Value
toJSON = ProgressUpdateEvent -> Value
forall a.
(Generic a, GToJSON Zero (Rep a), Typeable a) =>
a -> Value
genericToJSONWithModifier
data ProgressEndEvent
  = ProgressEndEvent
  { ProgressEndEvent -> Text
progressEndEventProgressId :: Text
    
    
    
  , ProgressEndEvent -> Maybe Text
progressEndEventMessage :: Maybe Text
    
    
    
    
  } deriving stock (Int -> ProgressEndEvent -> ShowS
[ProgressEndEvent] -> ShowS
ProgressEndEvent -> String
(Int -> ProgressEndEvent -> ShowS)
-> (ProgressEndEvent -> String)
-> ([ProgressEndEvent] -> ShowS)
-> Show ProgressEndEvent
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ProgressEndEvent -> ShowS
showsPrec :: Int -> ProgressEndEvent -> ShowS
$cshow :: ProgressEndEvent -> String
show :: ProgressEndEvent -> String
$cshowList :: [ProgressEndEvent] -> ShowS
showList :: [ProgressEndEvent] -> ShowS
Show, ProgressEndEvent -> ProgressEndEvent -> Bool
(ProgressEndEvent -> ProgressEndEvent -> Bool)
-> (ProgressEndEvent -> ProgressEndEvent -> Bool)
-> Eq ProgressEndEvent
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ProgressEndEvent -> ProgressEndEvent -> Bool
== :: ProgressEndEvent -> ProgressEndEvent -> Bool
$c/= :: ProgressEndEvent -> ProgressEndEvent -> Bool
/= :: ProgressEndEvent -> ProgressEndEvent -> Bool
Eq, (forall x. ProgressEndEvent -> Rep ProgressEndEvent x)
-> (forall x. Rep ProgressEndEvent x -> ProgressEndEvent)
-> Generic ProgressEndEvent
forall x. Rep ProgressEndEvent x -> ProgressEndEvent
forall x. ProgressEndEvent -> Rep ProgressEndEvent x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ProgressEndEvent -> Rep ProgressEndEvent x
from :: forall x. ProgressEndEvent -> Rep ProgressEndEvent x
$cto :: forall x. Rep ProgressEndEvent x -> ProgressEndEvent
to :: forall x. Rep ProgressEndEvent x -> ProgressEndEvent
Generic)
instance ToJSON ProgressEndEvent where
  toJSON :: ProgressEndEvent -> Value
toJSON = ProgressEndEvent -> Value
forall a.
(Generic a, GToJSON Zero (Rep a), Typeable a) =>
a -> Value
genericToJSONWithModifier
data InvalidatedEvent
  = InvalidatedEvent
  { InvalidatedEvent -> [InvalidatedAreas]
invalidatedEventAreas :: [InvalidatedAreas]
     
     
     
     
     
     
     
  , InvalidatedEvent -> Maybe Int
invalidatedEventThreadId :: Maybe Int
     
     
     
     
  , InvalidatedEvent -> Maybe Int
invalidatedEventStackFrameId :: Maybe Int
     
     
     
     
  } deriving stock (Int -> InvalidatedEvent -> ShowS
[InvalidatedEvent] -> ShowS
InvalidatedEvent -> String
(Int -> InvalidatedEvent -> ShowS)
-> (InvalidatedEvent -> String)
-> ([InvalidatedEvent] -> ShowS)
-> Show InvalidatedEvent
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> InvalidatedEvent -> ShowS
showsPrec :: Int -> InvalidatedEvent -> ShowS
$cshow :: InvalidatedEvent -> String
show :: InvalidatedEvent -> String
$cshowList :: [InvalidatedEvent] -> ShowS
showList :: [InvalidatedEvent] -> ShowS
Show, InvalidatedEvent -> InvalidatedEvent -> Bool
(InvalidatedEvent -> InvalidatedEvent -> Bool)
-> (InvalidatedEvent -> InvalidatedEvent -> Bool)
-> Eq InvalidatedEvent
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: InvalidatedEvent -> InvalidatedEvent -> Bool
== :: InvalidatedEvent -> InvalidatedEvent -> Bool
$c/= :: InvalidatedEvent -> InvalidatedEvent -> Bool
/= :: InvalidatedEvent -> InvalidatedEvent -> Bool
Eq, (forall x. InvalidatedEvent -> Rep InvalidatedEvent x)
-> (forall x. Rep InvalidatedEvent x -> InvalidatedEvent)
-> Generic InvalidatedEvent
forall x. Rep InvalidatedEvent x -> InvalidatedEvent
forall x. InvalidatedEvent -> Rep InvalidatedEvent x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. InvalidatedEvent -> Rep InvalidatedEvent x
from :: forall x. InvalidatedEvent -> Rep InvalidatedEvent x
$cto :: forall x. Rep InvalidatedEvent x -> InvalidatedEvent
to :: forall x. Rep InvalidatedEvent x -> InvalidatedEvent
Generic)
instance ToJSON InvalidatedEvent where
  toJSON :: InvalidatedEvent -> Value
toJSON = InvalidatedEvent -> Value
forall a.
(Generic a, GToJSON Zero (Rep a), Typeable a) =>
a -> Value
genericToJSONWithModifier
data InvalidatedAreas
  = InvalidatedAreasAll
  | InvalidatedAreasStacks
  | InvalidatedAreasThreads
  | InvalidatedAreasVariables
  deriving stock (Int -> InvalidatedAreas -> ShowS
[InvalidatedAreas] -> ShowS
InvalidatedAreas -> String
(Int -> InvalidatedAreas -> ShowS)
-> (InvalidatedAreas -> String)
-> ([InvalidatedAreas] -> ShowS)
-> Show InvalidatedAreas
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> InvalidatedAreas -> ShowS
showsPrec :: Int -> InvalidatedAreas -> ShowS
$cshow :: InvalidatedAreas -> String
show :: InvalidatedAreas -> String
$cshowList :: [InvalidatedAreas] -> ShowS
showList :: [InvalidatedAreas] -> ShowS
Show, InvalidatedAreas -> InvalidatedAreas -> Bool
(InvalidatedAreas -> InvalidatedAreas -> Bool)
-> (InvalidatedAreas -> InvalidatedAreas -> Bool)
-> Eq InvalidatedAreas
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: InvalidatedAreas -> InvalidatedAreas -> Bool
== :: InvalidatedAreas -> InvalidatedAreas -> Bool
$c/= :: InvalidatedAreas -> InvalidatedAreas -> Bool
/= :: InvalidatedAreas -> InvalidatedAreas -> Bool
Eq, (forall x. InvalidatedAreas -> Rep InvalidatedAreas x)
-> (forall x. Rep InvalidatedAreas x -> InvalidatedAreas)
-> Generic InvalidatedAreas
forall x. Rep InvalidatedAreas x -> InvalidatedAreas
forall x. InvalidatedAreas -> Rep InvalidatedAreas x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. InvalidatedAreas -> Rep InvalidatedAreas x
from :: forall x. InvalidatedAreas -> Rep InvalidatedAreas x
$cto :: forall x. Rep InvalidatedAreas x -> InvalidatedAreas
to :: forall x. Rep InvalidatedAreas x -> InvalidatedAreas
Generic)
instance ToJSON InvalidatedAreas where
  toJSON :: InvalidatedAreas -> Value
toJSON = InvalidatedAreas -> Value
forall a.
(Generic a, GToJSON Zero (Rep a), Typeable a) =>
a -> Value
genericToJSONWithModifier
data MemoryEvent
  = MemoryEvent
  { MemoryEvent -> Text
memoryEventMemoryReference :: Text
    
    
    
  , MemoryEvent -> Int
memoryEventOffset :: Int
    
    
    
  , MemoryEvent -> Int
memoryEventCount :: Int
    
    
    
  } deriving stock (Int -> MemoryEvent -> ShowS
[MemoryEvent] -> ShowS
MemoryEvent -> String
(Int -> MemoryEvent -> ShowS)
-> (MemoryEvent -> String)
-> ([MemoryEvent] -> ShowS)
-> Show MemoryEvent
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> MemoryEvent -> ShowS
showsPrec :: Int -> MemoryEvent -> ShowS
$cshow :: MemoryEvent -> String
show :: MemoryEvent -> String
$cshowList :: [MemoryEvent] -> ShowS
showList :: [MemoryEvent] -> ShowS
Show, MemoryEvent -> MemoryEvent -> Bool
(MemoryEvent -> MemoryEvent -> Bool)
-> (MemoryEvent -> MemoryEvent -> Bool) -> Eq MemoryEvent
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: MemoryEvent -> MemoryEvent -> Bool
== :: MemoryEvent -> MemoryEvent -> Bool
$c/= :: MemoryEvent -> MemoryEvent -> Bool
/= :: MemoryEvent -> MemoryEvent -> Bool
Eq, (forall x. MemoryEvent -> Rep MemoryEvent x)
-> (forall x. Rep MemoryEvent x -> MemoryEvent)
-> Generic MemoryEvent
forall x. Rep MemoryEvent x -> MemoryEvent
forall x. MemoryEvent -> Rep MemoryEvent x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. MemoryEvent -> Rep MemoryEvent x
from :: forall x. MemoryEvent -> Rep MemoryEvent x
$cto :: forall x. Rep MemoryEvent x -> MemoryEvent
to :: forall x. Rep MemoryEvent x -> MemoryEvent
Generic)
instance ToJSON MemoryEvent where
  toJSON :: MemoryEvent -> Value
toJSON = MemoryEvent -> Value
forall a.
(Generic a, GToJSON Zero (Rep a), Typeable a) =>
a -> Value
genericToJSONWithModifier
data CancelArguments
  = CancelArguments
  { CancelArguments -> Maybe Int
cancelArgumentsRequestId :: Maybe Int
    
    
    
    
    
  , CancelArguments -> Maybe Text
cancelArgumentsProgressId :: Maybe Text
    
    
    
    
    
  } deriving stock (Int -> CancelArguments -> ShowS
[CancelArguments] -> ShowS
CancelArguments -> String
(Int -> CancelArguments -> ShowS)
-> (CancelArguments -> String)
-> ([CancelArguments] -> ShowS)
-> Show CancelArguments
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CancelArguments -> ShowS
showsPrec :: Int -> CancelArguments -> ShowS
$cshow :: CancelArguments -> String
show :: CancelArguments -> String
$cshowList :: [CancelArguments] -> ShowS
showList :: [CancelArguments] -> ShowS
Show, CancelArguments -> CancelArguments -> Bool
(CancelArguments -> CancelArguments -> Bool)
-> (CancelArguments -> CancelArguments -> Bool)
-> Eq CancelArguments
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CancelArguments -> CancelArguments -> Bool
== :: CancelArguments -> CancelArguments -> Bool
$c/= :: CancelArguments -> CancelArguments -> Bool
/= :: CancelArguments -> CancelArguments -> Bool
Eq, (forall x. CancelArguments -> Rep CancelArguments x)
-> (forall x. Rep CancelArguments x -> CancelArguments)
-> Generic CancelArguments
forall x. Rep CancelArguments x -> CancelArguments
forall x. CancelArguments -> Rep CancelArguments x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. CancelArguments -> Rep CancelArguments x
from :: forall x. CancelArguments -> Rep CancelArguments x
$cto :: forall x. Rep CancelArguments x -> CancelArguments
to :: forall x. Rep CancelArguments x -> CancelArguments
Generic)
instance FromJSON CancelArguments where
  parseJSON :: Value -> Parser CancelArguments
parseJSON = Value -> Parser CancelArguments
forall a.
(Generic a, GFromJSON Zero (Rep a), Typeable a) =>
Value -> Parser a
genericParseJSONWithModifier
data RunInTerminalRequestArgumentsKind
  = RunInTerminalRequestArgumentsKindIntegrated
  | RunInTerminalRequestArgumentsKindExternal
  deriving stock (Int -> RunInTerminalRequestArgumentsKind -> ShowS
[RunInTerminalRequestArgumentsKind] -> ShowS
RunInTerminalRequestArgumentsKind -> String
(Int -> RunInTerminalRequestArgumentsKind -> ShowS)
-> (RunInTerminalRequestArgumentsKind -> String)
-> ([RunInTerminalRequestArgumentsKind] -> ShowS)
-> Show RunInTerminalRequestArgumentsKind
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RunInTerminalRequestArgumentsKind -> ShowS
showsPrec :: Int -> RunInTerminalRequestArgumentsKind -> ShowS
$cshow :: RunInTerminalRequestArgumentsKind -> String
show :: RunInTerminalRequestArgumentsKind -> String
$cshowList :: [RunInTerminalRequestArgumentsKind] -> ShowS
showList :: [RunInTerminalRequestArgumentsKind] -> ShowS
Show, RunInTerminalRequestArgumentsKind
-> RunInTerminalRequestArgumentsKind -> Bool
(RunInTerminalRequestArgumentsKind
 -> RunInTerminalRequestArgumentsKind -> Bool)
-> (RunInTerminalRequestArgumentsKind
    -> RunInTerminalRequestArgumentsKind -> Bool)
-> Eq RunInTerminalRequestArgumentsKind
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RunInTerminalRequestArgumentsKind
-> RunInTerminalRequestArgumentsKind -> Bool
== :: RunInTerminalRequestArgumentsKind
-> RunInTerminalRequestArgumentsKind -> Bool
$c/= :: RunInTerminalRequestArgumentsKind
-> RunInTerminalRequestArgumentsKind -> Bool
/= :: RunInTerminalRequestArgumentsKind
-> RunInTerminalRequestArgumentsKind -> Bool
Eq, (forall x.
 RunInTerminalRequestArgumentsKind
 -> Rep RunInTerminalRequestArgumentsKind x)
-> (forall x.
    Rep RunInTerminalRequestArgumentsKind x
    -> RunInTerminalRequestArgumentsKind)
-> Generic RunInTerminalRequestArgumentsKind
forall x.
Rep RunInTerminalRequestArgumentsKind x
-> RunInTerminalRequestArgumentsKind
forall x.
RunInTerminalRequestArgumentsKind
-> Rep RunInTerminalRequestArgumentsKind x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x.
RunInTerminalRequestArgumentsKind
-> Rep RunInTerminalRequestArgumentsKind x
from :: forall x.
RunInTerminalRequestArgumentsKind
-> Rep RunInTerminalRequestArgumentsKind x
$cto :: forall x.
Rep RunInTerminalRequestArgumentsKind x
-> RunInTerminalRequestArgumentsKind
to :: forall x.
Rep RunInTerminalRequestArgumentsKind x
-> RunInTerminalRequestArgumentsKind
Generic)
instance ToJSON RunInTerminalRequestArgumentsKind where
  toJSON :: RunInTerminalRequestArgumentsKind -> Value
toJSON = RunInTerminalRequestArgumentsKind -> Value
forall a.
(Generic a, GToJSON Zero (Rep a), Typeable a) =>
a -> Value
genericToJSONWithModifier
instance FromJSON RunInTerminalRequestArgumentsKind where
  parseJSON :: Value -> Parser RunInTerminalRequestArgumentsKind
parseJSON = Value -> Parser RunInTerminalRequestArgumentsKind
forall a.
(Generic a, GFromJSON Zero (Rep a), Typeable a) =>
Value -> Parser a
genericParseJSONWithModifier
data RunInTerminalRequestArguments
  = RunInTerminalRequestArguments
  { RunInTerminalRequestArguments
-> Maybe RunInTerminalRequestArgumentsKind
runInTerminalRequestArgumentsKind :: Maybe RunInTerminalRequestArgumentsKind
    
    
    
    
  , RunInTerminalRequestArguments -> Maybe Text
runInTerminalRequestArgumentsTitle :: Maybe Text
    
    
    
  , RunInTerminalRequestArguments -> Text
runInTerminalRequestArgumentsCwd :: Text
    
    
    
    
  , RunInTerminalRequestArguments -> [Text]
runInTerminalRequestArgumentsArgs :: [Text]
    
    
    
    
  , RunInTerminalRequestArguments -> Maybe (HashMap Text Text)
runInTerminalRequestArgumentsEnv :: Maybe (H.HashMap Text Text)
    
    
    
    
  , RunInTerminalRequestArguments -> Bool
runInTerminalRequestArgumentsArgsCanBeInterpretedByShell :: Bool
    
    
    
    
    
    
    
    
  } deriving stock (Int -> RunInTerminalRequestArguments -> ShowS
[RunInTerminalRequestArguments] -> ShowS
RunInTerminalRequestArguments -> String
(Int -> RunInTerminalRequestArguments -> ShowS)
-> (RunInTerminalRequestArguments -> String)
-> ([RunInTerminalRequestArguments] -> ShowS)
-> Show RunInTerminalRequestArguments
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RunInTerminalRequestArguments -> ShowS
showsPrec :: Int -> RunInTerminalRequestArguments -> ShowS
$cshow :: RunInTerminalRequestArguments -> String
show :: RunInTerminalRequestArguments -> String
$cshowList :: [RunInTerminalRequestArguments] -> ShowS
showList :: [RunInTerminalRequestArguments] -> ShowS
Show, RunInTerminalRequestArguments
-> RunInTerminalRequestArguments -> Bool
(RunInTerminalRequestArguments
 -> RunInTerminalRequestArguments -> Bool)
-> (RunInTerminalRequestArguments
    -> RunInTerminalRequestArguments -> Bool)
-> Eq RunInTerminalRequestArguments
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RunInTerminalRequestArguments
-> RunInTerminalRequestArguments -> Bool
== :: RunInTerminalRequestArguments
-> RunInTerminalRequestArguments -> Bool
$c/= :: RunInTerminalRequestArguments
-> RunInTerminalRequestArguments -> Bool
/= :: RunInTerminalRequestArguments
-> RunInTerminalRequestArguments -> Bool
Eq, (forall x.
 RunInTerminalRequestArguments
 -> Rep RunInTerminalRequestArguments x)
-> (forall x.
    Rep RunInTerminalRequestArguments x
    -> RunInTerminalRequestArguments)
-> Generic RunInTerminalRequestArguments
forall x.
Rep RunInTerminalRequestArguments x
-> RunInTerminalRequestArguments
forall x.
RunInTerminalRequestArguments
-> Rep RunInTerminalRequestArguments x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x.
RunInTerminalRequestArguments
-> Rep RunInTerminalRequestArguments x
from :: forall x.
RunInTerminalRequestArguments
-> Rep RunInTerminalRequestArguments x
$cto :: forall x.
Rep RunInTerminalRequestArguments x
-> RunInTerminalRequestArguments
to :: forall x.
Rep RunInTerminalRequestArguments x
-> RunInTerminalRequestArguments
Generic)
instance ToJSON RunInTerminalRequestArguments where
  toJSON :: RunInTerminalRequestArguments -> Value
toJSON = RunInTerminalRequestArguments -> Value
forall a.
(Generic a, GToJSON Zero (Rep a), Typeable a) =>
a -> Value
genericToJSONWithModifier
instance FromJSON RunInTerminalRequestArguments where
  parseJSON :: Value -> Parser RunInTerminalRequestArguments
parseJSON = Value -> Parser RunInTerminalRequestArguments
forall a.
(Generic a, GFromJSON Zero (Rep a), Typeable a) =>
Value -> Parser a
genericParseJSONWithModifier
data StartDebuggingRequestArgumentsConfiguration
  = StartDebuggingRequestArgumentsConfigurationLaunch
  | StartDebuggingRequestArgumentsConfigurationAttach
  deriving stock (Int -> StartDebuggingRequestArgumentsConfiguration -> ShowS
[StartDebuggingRequestArgumentsConfiguration] -> ShowS
StartDebuggingRequestArgumentsConfiguration -> String
(Int -> StartDebuggingRequestArgumentsConfiguration -> ShowS)
-> (StartDebuggingRequestArgumentsConfiguration -> String)
-> ([StartDebuggingRequestArgumentsConfiguration] -> ShowS)
-> Show StartDebuggingRequestArgumentsConfiguration
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> StartDebuggingRequestArgumentsConfiguration -> ShowS
showsPrec :: Int -> StartDebuggingRequestArgumentsConfiguration -> ShowS
$cshow :: StartDebuggingRequestArgumentsConfiguration -> String
show :: StartDebuggingRequestArgumentsConfiguration -> String
$cshowList :: [StartDebuggingRequestArgumentsConfiguration] -> ShowS
showList :: [StartDebuggingRequestArgumentsConfiguration] -> ShowS
Show, StartDebuggingRequestArgumentsConfiguration
-> StartDebuggingRequestArgumentsConfiguration -> Bool
(StartDebuggingRequestArgumentsConfiguration
 -> StartDebuggingRequestArgumentsConfiguration -> Bool)
-> (StartDebuggingRequestArgumentsConfiguration
    -> StartDebuggingRequestArgumentsConfiguration -> Bool)
-> Eq StartDebuggingRequestArgumentsConfiguration
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: StartDebuggingRequestArgumentsConfiguration
-> StartDebuggingRequestArgumentsConfiguration -> Bool
== :: StartDebuggingRequestArgumentsConfiguration
-> StartDebuggingRequestArgumentsConfiguration -> Bool
$c/= :: StartDebuggingRequestArgumentsConfiguration
-> StartDebuggingRequestArgumentsConfiguration -> Bool
/= :: StartDebuggingRequestArgumentsConfiguration
-> StartDebuggingRequestArgumentsConfiguration -> Bool
Eq, (forall x.
 StartDebuggingRequestArgumentsConfiguration
 -> Rep StartDebuggingRequestArgumentsConfiguration x)
-> (forall x.
    Rep StartDebuggingRequestArgumentsConfiguration x
    -> StartDebuggingRequestArgumentsConfiguration)
-> Generic StartDebuggingRequestArgumentsConfiguration
forall x.
Rep StartDebuggingRequestArgumentsConfiguration x
-> StartDebuggingRequestArgumentsConfiguration
forall x.
StartDebuggingRequestArgumentsConfiguration
-> Rep StartDebuggingRequestArgumentsConfiguration x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x.
StartDebuggingRequestArgumentsConfiguration
-> Rep StartDebuggingRequestArgumentsConfiguration x
from :: forall x.
StartDebuggingRequestArgumentsConfiguration
-> Rep StartDebuggingRequestArgumentsConfiguration x
$cto :: forall x.
Rep StartDebuggingRequestArgumentsConfiguration x
-> StartDebuggingRequestArgumentsConfiguration
to :: forall x.
Rep StartDebuggingRequestArgumentsConfiguration x
-> StartDebuggingRequestArgumentsConfiguration
Generic)
instance FromJSON StartDebuggingRequestArgumentsConfiguration where
  parseJSON :: Value -> Parser StartDebuggingRequestArgumentsConfiguration
parseJSON = Value -> Parser StartDebuggingRequestArgumentsConfiguration
forall a.
(Generic a, GFromJSON Zero (Rep a), Typeable a) =>
Value -> Parser a
genericParseJSONWithModifier
data StartDebuggingRequestArguments
  = StartDebuggingRequestArguments
  { StartDebuggingRequestArguments -> HashMap Text Value
startDebuggingRequestArgumentsConfiguration :: H.HashMap Text Value
    
    
    
    
    
    
  , StartDebuggingRequestArguments
-> StartDebuggingRequestArgumentsConfiguration
startDebuggingRequestArgumentsConfigurationRequest :: StartDebuggingRequestArgumentsConfiguration
    
    
    
    
    
  } deriving stock (Int -> StartDebuggingRequestArguments -> ShowS
[StartDebuggingRequestArguments] -> ShowS
StartDebuggingRequestArguments -> String
(Int -> StartDebuggingRequestArguments -> ShowS)
-> (StartDebuggingRequestArguments -> String)
-> ([StartDebuggingRequestArguments] -> ShowS)
-> Show StartDebuggingRequestArguments
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> StartDebuggingRequestArguments -> ShowS
showsPrec :: Int -> StartDebuggingRequestArguments -> ShowS
$cshow :: StartDebuggingRequestArguments -> String
show :: StartDebuggingRequestArguments -> String
$cshowList :: [StartDebuggingRequestArguments] -> ShowS
showList :: [StartDebuggingRequestArguments] -> ShowS
Show, StartDebuggingRequestArguments
-> StartDebuggingRequestArguments -> Bool
(StartDebuggingRequestArguments
 -> StartDebuggingRequestArguments -> Bool)
-> (StartDebuggingRequestArguments
    -> StartDebuggingRequestArguments -> Bool)
-> Eq StartDebuggingRequestArguments
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: StartDebuggingRequestArguments
-> StartDebuggingRequestArguments -> Bool
== :: StartDebuggingRequestArguments
-> StartDebuggingRequestArguments -> Bool
$c/= :: StartDebuggingRequestArguments
-> StartDebuggingRequestArguments -> Bool
/= :: StartDebuggingRequestArguments
-> StartDebuggingRequestArguments -> Bool
Eq, (forall x.
 StartDebuggingRequestArguments
 -> Rep StartDebuggingRequestArguments x)
-> (forall x.
    Rep StartDebuggingRequestArguments x
    -> StartDebuggingRequestArguments)
-> Generic StartDebuggingRequestArguments
forall x.
Rep StartDebuggingRequestArguments x
-> StartDebuggingRequestArguments
forall x.
StartDebuggingRequestArguments
-> Rep StartDebuggingRequestArguments x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x.
StartDebuggingRequestArguments
-> Rep StartDebuggingRequestArguments x
from :: forall x.
StartDebuggingRequestArguments
-> Rep StartDebuggingRequestArguments x
$cto :: forall x.
Rep StartDebuggingRequestArguments x
-> StartDebuggingRequestArguments
to :: forall x.
Rep StartDebuggingRequestArguments x
-> StartDebuggingRequestArguments
Generic)
instance FromJSON StartDebuggingRequestArguments where
  parseJSON :: Value -> Parser StartDebuggingRequestArguments
parseJSON = Value -> Parser StartDebuggingRequestArguments
forall a.
(Generic a, GFromJSON Zero (Rep a), Typeable a) =>
Value -> Parser a
genericParseJSONWithModifier
data PathFormat
  = Path
  | URI
  | PathFormat Text
  deriving stock (Int -> PathFormat -> ShowS
[PathFormat] -> ShowS
PathFormat -> String
(Int -> PathFormat -> ShowS)
-> (PathFormat -> String)
-> ([PathFormat] -> ShowS)
-> Show PathFormat
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> PathFormat -> ShowS
showsPrec :: Int -> PathFormat -> ShowS
$cshow :: PathFormat -> String
show :: PathFormat -> String
$cshowList :: [PathFormat] -> ShowS
showList :: [PathFormat] -> ShowS
Show, PathFormat -> PathFormat -> Bool
(PathFormat -> PathFormat -> Bool)
-> (PathFormat -> PathFormat -> Bool) -> Eq PathFormat
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: PathFormat -> PathFormat -> Bool
== :: PathFormat -> PathFormat -> Bool
$c/= :: PathFormat -> PathFormat -> Bool
/= :: PathFormat -> PathFormat -> Bool
Eq)
instance FromJSON PathFormat where
   parseJSON :: Value -> Parser PathFormat
parseJSON = String -> (Text -> Parser PathFormat) -> Value -> Parser PathFormat
forall a. String -> (Text -> Parser a) -> Value -> Parser a
withText String
"PathFormat" ((Text -> Parser PathFormat) -> Value -> Parser PathFormat)
-> (Text -> Parser PathFormat) -> Value -> Parser PathFormat
forall a b. (a -> b) -> a -> b
$ \Text
txt ->
     PathFormat -> Parser PathFormat
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PathFormat -> Parser PathFormat)
-> PathFormat -> Parser PathFormat
forall a b. (a -> b) -> a -> b
$ case Text
txt of
       Text
"path" -> PathFormat
Path
       Text
"uri"  -> PathFormat
URI
       Text
_      -> Text -> PathFormat
PathFormat Text
txt
data InitializeRequestArguments
  = InitializeRequestArguments
  { InitializeRequestArguments -> Maybe Text
clientID :: Maybe Text
    
    
    
  , InitializeRequestArguments -> Maybe Text
clientName :: Maybe Text
    
    
    
  , InitializeRequestArguments -> Text
adapterID :: Text
    
    
    
  , InitializeRequestArguments -> Maybe Text
locale :: Maybe Text
    
    
    
  , InitializeRequestArguments -> Maybe Bool
linesStartAt1 :: Maybe Bool
    
    
    
  , InitializeRequestArguments -> Maybe Bool
columnsStartAt1 :: Maybe Bool
    
    
    
  , InitializeRequestArguments -> Maybe PathFormat
pathFormat :: Maybe PathFormat
    
    
    
    
    
  , InitializeRequestArguments -> Maybe Bool
supportsVariableType :: Maybe Bool
    
    
    
  , InitializeRequestArguments -> Maybe Bool
supportsVariablePaging :: Maybe Bool
    
    
    
  , InitializeRequestArguments -> Maybe Bool
supportsRunInTerminalRequest :: Maybe Bool
    
    
    
  , InitializeRequestArguments -> Maybe Bool
supportsMemoryReferences :: Maybe Bool
    
    
    
  , InitializeRequestArguments -> Maybe Bool
supportsProgressReporting :: Maybe Bool
    
    
    
  , InitializeRequestArguments -> Maybe Bool
supportsInvalidatedEvent :: Maybe Bool
    
    
    
  , InitializeRequestArguments -> Maybe Bool
supportsMemoryEvent :: Maybe Bool
    
    
    
  , InitializeRequestArguments -> Maybe Bool
supportsArgsCanBeInterpretedByShell :: Maybe Bool
    
    
    
    
  , InitializeRequestArguments -> Maybe Bool
supportsStartDebuggingRequest :: Maybe Bool
    
    
    
  , InitializeRequestArguments -> Maybe Bool
supportsANSIStyling :: Maybe Bool
    
    
    
    
    
  } deriving stock (Int -> InitializeRequestArguments -> ShowS
[InitializeRequestArguments] -> ShowS
InitializeRequestArguments -> String
(Int -> InitializeRequestArguments -> ShowS)
-> (InitializeRequestArguments -> String)
-> ([InitializeRequestArguments] -> ShowS)
-> Show InitializeRequestArguments
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> InitializeRequestArguments -> ShowS
showsPrec :: Int -> InitializeRequestArguments -> ShowS
$cshow :: InitializeRequestArguments -> String
show :: InitializeRequestArguments -> String
$cshowList :: [InitializeRequestArguments] -> ShowS
showList :: [InitializeRequestArguments] -> ShowS
Show, InitializeRequestArguments -> InitializeRequestArguments -> Bool
(InitializeRequestArguments -> InitializeRequestArguments -> Bool)
-> (InitializeRequestArguments
    -> InitializeRequestArguments -> Bool)
-> Eq InitializeRequestArguments
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: InitializeRequestArguments -> InitializeRequestArguments -> Bool
== :: InitializeRequestArguments -> InitializeRequestArguments -> Bool
$c/= :: InitializeRequestArguments -> InitializeRequestArguments -> Bool
/= :: InitializeRequestArguments -> InitializeRequestArguments -> Bool
Eq, (forall x.
 InitializeRequestArguments -> Rep InitializeRequestArguments x)
-> (forall x.
    Rep InitializeRequestArguments x -> InitializeRequestArguments)
-> Generic InitializeRequestArguments
forall x.
Rep InitializeRequestArguments x -> InitializeRequestArguments
forall x.
InitializeRequestArguments -> Rep InitializeRequestArguments x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x.
InitializeRequestArguments -> Rep InitializeRequestArguments x
from :: forall x.
InitializeRequestArguments -> Rep InitializeRequestArguments x
$cto :: forall x.
Rep InitializeRequestArguments x -> InitializeRequestArguments
to :: forall x.
Rep InitializeRequestArguments x -> InitializeRequestArguments
Generic)
instance FromJSON InitializeRequestArguments where
  parseJSON :: Value -> Parser InitializeRequestArguments
parseJSON = Options -> Value -> Parser InitializeRequestArguments
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON Options
defaultOptions
data LaunchRequestArguments
  = LaunchRequestArguments
  { LaunchRequestArguments -> Bool
launchRequestArgumentsNoDebug :: Bool
    
    
    
    
  , LaunchRequestArguments -> Maybe Value
launchRequestArgumentsRestart :: Maybe Value
    
    
    
    
    
  } deriving stock (Int -> LaunchRequestArguments -> ShowS
[LaunchRequestArguments] -> ShowS
LaunchRequestArguments -> String
(Int -> LaunchRequestArguments -> ShowS)
-> (LaunchRequestArguments -> String)
-> ([LaunchRequestArguments] -> ShowS)
-> Show LaunchRequestArguments
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> LaunchRequestArguments -> ShowS
showsPrec :: Int -> LaunchRequestArguments -> ShowS
$cshow :: LaunchRequestArguments -> String
show :: LaunchRequestArguments -> String
$cshowList :: [LaunchRequestArguments] -> ShowS
showList :: [LaunchRequestArguments] -> ShowS
Show, LaunchRequestArguments -> LaunchRequestArguments -> Bool
(LaunchRequestArguments -> LaunchRequestArguments -> Bool)
-> (LaunchRequestArguments -> LaunchRequestArguments -> Bool)
-> Eq LaunchRequestArguments
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: LaunchRequestArguments -> LaunchRequestArguments -> Bool
== :: LaunchRequestArguments -> LaunchRequestArguments -> Bool
$c/= :: LaunchRequestArguments -> LaunchRequestArguments -> Bool
/= :: LaunchRequestArguments -> LaunchRequestArguments -> Bool
Eq, (forall x. LaunchRequestArguments -> Rep LaunchRequestArguments x)
-> (forall x.
    Rep LaunchRequestArguments x -> LaunchRequestArguments)
-> Generic LaunchRequestArguments
forall x. Rep LaunchRequestArguments x -> LaunchRequestArguments
forall x. LaunchRequestArguments -> Rep LaunchRequestArguments x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. LaunchRequestArguments -> Rep LaunchRequestArguments x
from :: forall x. LaunchRequestArguments -> Rep LaunchRequestArguments x
$cto :: forall x. Rep LaunchRequestArguments x -> LaunchRequestArguments
to :: forall x. Rep LaunchRequestArguments x -> LaunchRequestArguments
Generic)
instance FromJSON LaunchRequestArguments where
  parseJSON :: Value -> Parser LaunchRequestArguments
parseJSON = Value -> Parser LaunchRequestArguments
forall a.
(Generic a, GFromJSON Zero (Rep a), Typeable a) =>
Value -> Parser a
genericParseJSONWithModifier
data AttachRequestArguments
  = AttachRequestArguments
  { AttachRequestArguments -> Maybe Value
attachRequestArgumentsRestart :: Maybe Value
    
    
    
    
    
  } deriving stock (Int -> AttachRequestArguments -> ShowS
[AttachRequestArguments] -> ShowS
AttachRequestArguments -> String
(Int -> AttachRequestArguments -> ShowS)
-> (AttachRequestArguments -> String)
-> ([AttachRequestArguments] -> ShowS)
-> Show AttachRequestArguments
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> AttachRequestArguments -> ShowS
showsPrec :: Int -> AttachRequestArguments -> ShowS
$cshow :: AttachRequestArguments -> String
show :: AttachRequestArguments -> String
$cshowList :: [AttachRequestArguments] -> ShowS
showList :: [AttachRequestArguments] -> ShowS
Show, AttachRequestArguments -> AttachRequestArguments -> Bool
(AttachRequestArguments -> AttachRequestArguments -> Bool)
-> (AttachRequestArguments -> AttachRequestArguments -> Bool)
-> Eq AttachRequestArguments
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: AttachRequestArguments -> AttachRequestArguments -> Bool
== :: AttachRequestArguments -> AttachRequestArguments -> Bool
$c/= :: AttachRequestArguments -> AttachRequestArguments -> Bool
/= :: AttachRequestArguments -> AttachRequestArguments -> Bool
Eq, (forall x. AttachRequestArguments -> Rep AttachRequestArguments x)
-> (forall x.
    Rep AttachRequestArguments x -> AttachRequestArguments)
-> Generic AttachRequestArguments
forall x. Rep AttachRequestArguments x -> AttachRequestArguments
forall x. AttachRequestArguments -> Rep AttachRequestArguments x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. AttachRequestArguments -> Rep AttachRequestArguments x
from :: forall x. AttachRequestArguments -> Rep AttachRequestArguments x
$cto :: forall x. Rep AttachRequestArguments x -> AttachRequestArguments
to :: forall x. Rep AttachRequestArguments x -> AttachRequestArguments
Generic)
instance FromJSON AttachRequestArguments where
  parseJSON :: Value -> Parser AttachRequestArguments
parseJSON = Value -> Parser AttachRequestArguments
forall a.
(Generic a, GFromJSON Zero (Rep a), Typeable a) =>
Value -> Parser a
genericParseJSONWithModifier
data RestartArguments
  = RestartArguments
  { RestartArguments
-> Maybe (Either LaunchRequestArguments AttachRequestArguments)
restartArgumentsArguments :: Maybe (Either LaunchRequestArguments AttachRequestArguments)
    
    
    
  } deriving stock (Int -> RestartArguments -> ShowS
[RestartArguments] -> ShowS
RestartArguments -> String
(Int -> RestartArguments -> ShowS)
-> (RestartArguments -> String)
-> ([RestartArguments] -> ShowS)
-> Show RestartArguments
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RestartArguments -> ShowS
showsPrec :: Int -> RestartArguments -> ShowS
$cshow :: RestartArguments -> String
show :: RestartArguments -> String
$cshowList :: [RestartArguments] -> ShowS
showList :: [RestartArguments] -> ShowS
Show, RestartArguments -> RestartArguments -> Bool
(RestartArguments -> RestartArguments -> Bool)
-> (RestartArguments -> RestartArguments -> Bool)
-> Eq RestartArguments
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RestartArguments -> RestartArguments -> Bool
== :: RestartArguments -> RestartArguments -> Bool
$c/= :: RestartArguments -> RestartArguments -> Bool
/= :: RestartArguments -> RestartArguments -> Bool
Eq, (forall x. RestartArguments -> Rep RestartArguments x)
-> (forall x. Rep RestartArguments x -> RestartArguments)
-> Generic RestartArguments
forall x. Rep RestartArguments x -> RestartArguments
forall x. RestartArguments -> Rep RestartArguments x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. RestartArguments -> Rep RestartArguments x
from :: forall x. RestartArguments -> Rep RestartArguments x
$cto :: forall x. Rep RestartArguments x -> RestartArguments
to :: forall x. Rep RestartArguments x -> RestartArguments
Generic)
instance FromJSON RestartArguments where
  parseJSON :: Value -> Parser RestartArguments
parseJSON = String
-> (Object -> Parser RestartArguments)
-> Value
-> Parser RestartArguments
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"RestartArguments" ((Object -> Parser RestartArguments)
 -> Value -> Parser RestartArguments)
-> (Object -> Parser RestartArguments)
-> Value
-> Parser RestartArguments
forall a b. (a -> b) -> a -> b
$ \Object
o -> do
     Object
o Object -> Key -> Parser (Maybe Value)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"arguments" Parser (Maybe Value)
-> (Maybe Value -> Parser RestartArguments)
-> Parser RestartArguments
forall a b. Parser a -> (a -> Parser b) -> Parser b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
       Maybe Value
Nothing ->
         RestartArguments -> Parser RestartArguments
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Maybe (Either LaunchRequestArguments AttachRequestArguments)
-> RestartArguments
RestartArguments Maybe (Either LaunchRequestArguments AttachRequestArguments)
forall a. Maybe a
Nothing)
       Just Value
r -> do
         Either LaunchRequestArguments AttachRequestArguments
value <- LaunchRequestArguments
-> Either LaunchRequestArguments AttachRequestArguments
forall a b. a -> Either a b
Left (LaunchRequestArguments
 -> Either LaunchRequestArguments AttachRequestArguments)
-> Parser LaunchRequestArguments
-> Parser (Either LaunchRequestArguments AttachRequestArguments)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser LaunchRequestArguments
forall a. FromJSON a => Value -> Parser a
parseJSON Value
r Parser (Either LaunchRequestArguments AttachRequestArguments)
-> Parser (Either LaunchRequestArguments AttachRequestArguments)
-> Parser (Either LaunchRequestArguments AttachRequestArguments)
forall a. Parser a -> Parser a -> Parser a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> AttachRequestArguments
-> Either LaunchRequestArguments AttachRequestArguments
forall a b. b -> Either a b
Right (AttachRequestArguments
 -> Either LaunchRequestArguments AttachRequestArguments)
-> Parser AttachRequestArguments
-> Parser (Either LaunchRequestArguments AttachRequestArguments)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser AttachRequestArguments
forall a. FromJSON a => Value -> Parser a
parseJSON Value
r
         RestartArguments -> Parser RestartArguments
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (RestartArguments -> Parser RestartArguments)
-> RestartArguments -> Parser RestartArguments
forall a b. (a -> b) -> a -> b
$ Maybe (Either LaunchRequestArguments AttachRequestArguments)
-> RestartArguments
RestartArguments (Either LaunchRequestArguments AttachRequestArguments
-> Maybe (Either LaunchRequestArguments AttachRequestArguments)
forall a. a -> Maybe a
Just Either LaunchRequestArguments AttachRequestArguments
value)
data DisconnectArguments
  = DisconnectArguments
  { DisconnectArguments -> Bool
disconnectArgumentsRestart :: Bool
    
    
    
    
  , DisconnectArguments -> Bool
disconnectArgumentsTerminateDebuggee :: Bool
    
    
    
    
    
    
    
  , DisconnectArguments -> Bool
disconnectArgumentsSuspendDebuggee :: Bool
    
    
    
    
    
    
    
  } deriving stock (Int -> DisconnectArguments -> ShowS
[DisconnectArguments] -> ShowS
DisconnectArguments -> String
(Int -> DisconnectArguments -> ShowS)
-> (DisconnectArguments -> String)
-> ([DisconnectArguments] -> ShowS)
-> Show DisconnectArguments
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> DisconnectArguments -> ShowS
showsPrec :: Int -> DisconnectArguments -> ShowS
$cshow :: DisconnectArguments -> String
show :: DisconnectArguments -> String
$cshowList :: [DisconnectArguments] -> ShowS
showList :: [DisconnectArguments] -> ShowS
Show, DisconnectArguments -> DisconnectArguments -> Bool
(DisconnectArguments -> DisconnectArguments -> Bool)
-> (DisconnectArguments -> DisconnectArguments -> Bool)
-> Eq DisconnectArguments
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DisconnectArguments -> DisconnectArguments -> Bool
== :: DisconnectArguments -> DisconnectArguments -> Bool
$c/= :: DisconnectArguments -> DisconnectArguments -> Bool
/= :: DisconnectArguments -> DisconnectArguments -> Bool
Eq, (forall x. DisconnectArguments -> Rep DisconnectArguments x)
-> (forall x. Rep DisconnectArguments x -> DisconnectArguments)
-> Generic DisconnectArguments
forall x. Rep DisconnectArguments x -> DisconnectArguments
forall x. DisconnectArguments -> Rep DisconnectArguments x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. DisconnectArguments -> Rep DisconnectArguments x
from :: forall x. DisconnectArguments -> Rep DisconnectArguments x
$cto :: forall x. Rep DisconnectArguments x -> DisconnectArguments
to :: forall x. Rep DisconnectArguments x -> DisconnectArguments
Generic)
instance FromJSON DisconnectArguments where
  parseJSON :: Value -> Parser DisconnectArguments
parseJSON = Value -> Parser DisconnectArguments
forall a.
(Generic a, GFromJSON Zero (Rep a), Typeable a) =>
Value -> Parser a
genericParseJSONWithModifier
data TerminateArguments
  = TerminateArguments
  { TerminateArguments -> Bool
terminateArgumentsRestart :: Bool
    
    
    
    
  } deriving stock (Int -> TerminateArguments -> ShowS
[TerminateArguments] -> ShowS
TerminateArguments -> String
(Int -> TerminateArguments -> ShowS)
-> (TerminateArguments -> String)
-> ([TerminateArguments] -> ShowS)
-> Show TerminateArguments
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TerminateArguments -> ShowS
showsPrec :: Int -> TerminateArguments -> ShowS
$cshow :: TerminateArguments -> String
show :: TerminateArguments -> String
$cshowList :: [TerminateArguments] -> ShowS
showList :: [TerminateArguments] -> ShowS
Show, TerminateArguments -> TerminateArguments -> Bool
(TerminateArguments -> TerminateArguments -> Bool)
-> (TerminateArguments -> TerminateArguments -> Bool)
-> Eq TerminateArguments
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TerminateArguments -> TerminateArguments -> Bool
== :: TerminateArguments -> TerminateArguments -> Bool
$c/= :: TerminateArguments -> TerminateArguments -> Bool
/= :: TerminateArguments -> TerminateArguments -> Bool
Eq, (forall x. TerminateArguments -> Rep TerminateArguments x)
-> (forall x. Rep TerminateArguments x -> TerminateArguments)
-> Generic TerminateArguments
forall x. Rep TerminateArguments x -> TerminateArguments
forall x. TerminateArguments -> Rep TerminateArguments x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. TerminateArguments -> Rep TerminateArguments x
from :: forall x. TerminateArguments -> Rep TerminateArguments x
$cto :: forall x. Rep TerminateArguments x -> TerminateArguments
to :: forall x. Rep TerminateArguments x -> TerminateArguments
Generic)
instance FromJSON TerminateArguments where
  parseJSON :: Value -> Parser TerminateArguments
parseJSON = Value -> Parser TerminateArguments
forall a.
(Generic a, GFromJSON Zero (Rep a), Typeable a) =>
Value -> Parser a
genericParseJSONWithModifier
data BreakpointLocationsArguments
  = BreakpointLocationsArguments
  { BreakpointLocationsArguments -> Source
breakpointLocationsArgumentsSource :: Source
    
    
    
    
  , BreakpointLocationsArguments -> Int
breakpointLocationsArgumentsLine :: Int
    
    
    
    
  , BreakpointLocationsArguments -> Maybe Int
breakpointLocationsArgumentsColumn :: Maybe Int
    
    
    
    
    
    
  , BreakpointLocationsArguments -> Maybe Int
breakpointLocationsArgumentsEndLine :: Maybe Int
    
    
    
    
  , BreakpointLocationsArguments -> Maybe Int
breakpointLocationsArgumentsEndColumn :: Maybe Int
    
    
    
    
    
    
  } deriving stock (Int -> BreakpointLocationsArguments -> ShowS
[BreakpointLocationsArguments] -> ShowS
BreakpointLocationsArguments -> String
(Int -> BreakpointLocationsArguments -> ShowS)
-> (BreakpointLocationsArguments -> String)
-> ([BreakpointLocationsArguments] -> ShowS)
-> Show BreakpointLocationsArguments
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> BreakpointLocationsArguments -> ShowS
showsPrec :: Int -> BreakpointLocationsArguments -> ShowS
$cshow :: BreakpointLocationsArguments -> String
show :: BreakpointLocationsArguments -> String
$cshowList :: [BreakpointLocationsArguments] -> ShowS
showList :: [BreakpointLocationsArguments] -> ShowS
Show, BreakpointLocationsArguments
-> BreakpointLocationsArguments -> Bool
(BreakpointLocationsArguments
 -> BreakpointLocationsArguments -> Bool)
-> (BreakpointLocationsArguments
    -> BreakpointLocationsArguments -> Bool)
-> Eq BreakpointLocationsArguments
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: BreakpointLocationsArguments
-> BreakpointLocationsArguments -> Bool
== :: BreakpointLocationsArguments
-> BreakpointLocationsArguments -> Bool
$c/= :: BreakpointLocationsArguments
-> BreakpointLocationsArguments -> Bool
/= :: BreakpointLocationsArguments
-> BreakpointLocationsArguments -> Bool
Eq, (forall x.
 BreakpointLocationsArguments -> Rep BreakpointLocationsArguments x)
-> (forall x.
    Rep BreakpointLocationsArguments x -> BreakpointLocationsArguments)
-> Generic BreakpointLocationsArguments
forall x.
Rep BreakpointLocationsArguments x -> BreakpointLocationsArguments
forall x.
BreakpointLocationsArguments -> Rep BreakpointLocationsArguments x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x.
BreakpointLocationsArguments -> Rep BreakpointLocationsArguments x
from :: forall x.
BreakpointLocationsArguments -> Rep BreakpointLocationsArguments x
$cto :: forall x.
Rep BreakpointLocationsArguments x -> BreakpointLocationsArguments
to :: forall x.
Rep BreakpointLocationsArguments x -> BreakpointLocationsArguments
Generic)
instance FromJSON BreakpointLocationsArguments where
  parseJSON :: Value -> Parser BreakpointLocationsArguments
parseJSON = Value -> Parser BreakpointLocationsArguments
forall a.
(Generic a, GFromJSON Zero (Rep a), Typeable a) =>
Value -> Parser a
genericParseJSONWithModifier
data SetBreakpointsArguments
  = SetBreakpointsArguments
  { SetBreakpointsArguments -> Source
setBreakpointsArgumentsSource :: Source
    
    
    
    
  , SetBreakpointsArguments -> Maybe [SourceBreakpoint]
setBreakpointsArgumentsBreakpoints :: Maybe [SourceBreakpoint]
    
    
    
  , SetBreakpointsArguments -> Maybe [Int]
setBreakpointsArgumentsLines :: Maybe [Int]
    
    
    
  , SetBreakpointsArguments -> Maybe Bool
setBreakpointsArgumentsSourceModified :: Maybe Bool
    
    
    
    
  } deriving stock (Int -> SetBreakpointsArguments -> ShowS
[SetBreakpointsArguments] -> ShowS
SetBreakpointsArguments -> String
(Int -> SetBreakpointsArguments -> ShowS)
-> (SetBreakpointsArguments -> String)
-> ([SetBreakpointsArguments] -> ShowS)
-> Show SetBreakpointsArguments
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SetBreakpointsArguments -> ShowS
showsPrec :: Int -> SetBreakpointsArguments -> ShowS
$cshow :: SetBreakpointsArguments -> String
show :: SetBreakpointsArguments -> String
$cshowList :: [SetBreakpointsArguments] -> ShowS
showList :: [SetBreakpointsArguments] -> ShowS
Show, SetBreakpointsArguments -> SetBreakpointsArguments -> Bool
(SetBreakpointsArguments -> SetBreakpointsArguments -> Bool)
-> (SetBreakpointsArguments -> SetBreakpointsArguments -> Bool)
-> Eq SetBreakpointsArguments
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SetBreakpointsArguments -> SetBreakpointsArguments -> Bool
== :: SetBreakpointsArguments -> SetBreakpointsArguments -> Bool
$c/= :: SetBreakpointsArguments -> SetBreakpointsArguments -> Bool
/= :: SetBreakpointsArguments -> SetBreakpointsArguments -> Bool
Eq, (forall x.
 SetBreakpointsArguments -> Rep SetBreakpointsArguments x)
-> (forall x.
    Rep SetBreakpointsArguments x -> SetBreakpointsArguments)
-> Generic SetBreakpointsArguments
forall x. Rep SetBreakpointsArguments x -> SetBreakpointsArguments
forall x. SetBreakpointsArguments -> Rep SetBreakpointsArguments x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. SetBreakpointsArguments -> Rep SetBreakpointsArguments x
from :: forall x. SetBreakpointsArguments -> Rep SetBreakpointsArguments x
$cto :: forall x. Rep SetBreakpointsArguments x -> SetBreakpointsArguments
to :: forall x. Rep SetBreakpointsArguments x -> SetBreakpointsArguments
Generic)
instance FromJSON SetBreakpointsArguments where
  parseJSON :: Value -> Parser SetBreakpointsArguments
parseJSON = Value -> Parser SetBreakpointsArguments
forall a.
(Generic a, GFromJSON Zero (Rep a), Typeable a) =>
Value -> Parser a
genericParseJSONWithModifier
data SourceBreakpoint
  = SourceBreakpoint
  { SourceBreakpoint -> Int
sourceBreakpointLine :: Int
    
    
    
  , SourceBreakpoint -> Maybe Int
sourceBreakpointColumn :: Maybe Int
    
    
    
    
    
  , SourceBreakpoint -> Maybe Text
sourceBreakpointCondition :: Maybe Text
    
    
    
    
    
  , SourceBreakpoint -> Maybe Text
sourceBreakpointHitCondition :: Maybe Text
    
    
    
    
    
    
    
    
    
  , SourceBreakpoint -> Maybe Text
sourceBreakpointLogMessage :: Maybe Text
    
    
    
    
    
    
    
    
    
  } deriving stock (Int -> SourceBreakpoint -> ShowS
[SourceBreakpoint] -> ShowS
SourceBreakpoint -> String
(Int -> SourceBreakpoint -> ShowS)
-> (SourceBreakpoint -> String)
-> ([SourceBreakpoint] -> ShowS)
-> Show SourceBreakpoint
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SourceBreakpoint -> ShowS
showsPrec :: Int -> SourceBreakpoint -> ShowS
$cshow :: SourceBreakpoint -> String
show :: SourceBreakpoint -> String
$cshowList :: [SourceBreakpoint] -> ShowS
showList :: [SourceBreakpoint] -> ShowS
Show, SourceBreakpoint -> SourceBreakpoint -> Bool
(SourceBreakpoint -> SourceBreakpoint -> Bool)
-> (SourceBreakpoint -> SourceBreakpoint -> Bool)
-> Eq SourceBreakpoint
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SourceBreakpoint -> SourceBreakpoint -> Bool
== :: SourceBreakpoint -> SourceBreakpoint -> Bool
$c/= :: SourceBreakpoint -> SourceBreakpoint -> Bool
/= :: SourceBreakpoint -> SourceBreakpoint -> Bool
Eq, (forall x. SourceBreakpoint -> Rep SourceBreakpoint x)
-> (forall x. Rep SourceBreakpoint x -> SourceBreakpoint)
-> Generic SourceBreakpoint
forall x. Rep SourceBreakpoint x -> SourceBreakpoint
forall x. SourceBreakpoint -> Rep SourceBreakpoint x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. SourceBreakpoint -> Rep SourceBreakpoint x
from :: forall x. SourceBreakpoint -> Rep SourceBreakpoint x
$cto :: forall x. Rep SourceBreakpoint x -> SourceBreakpoint
to :: forall x. Rep SourceBreakpoint x -> SourceBreakpoint
Generic)
defaultSourceBreakpoint :: SourceBreakpoint
defaultSourceBreakpoint :: SourceBreakpoint
defaultSourceBreakpoint
  = SourceBreakpoint
  { sourceBreakpointLine :: Int
sourceBreakpointLine = Int
0
  , sourceBreakpointColumn :: Maybe Int
sourceBreakpointColumn = Maybe Int
forall a. Maybe a
Nothing
  , sourceBreakpointCondition :: Maybe Text
sourceBreakpointCondition = Maybe Text
forall a. Maybe a
Nothing
  , sourceBreakpointHitCondition :: Maybe Text
sourceBreakpointHitCondition = Maybe Text
forall a. Maybe a
Nothing
  , sourceBreakpointLogMessage :: Maybe Text
sourceBreakpointLogMessage = Maybe Text
forall a. Maybe a
Nothing
  }
instance FromJSON SourceBreakpoint where
  parseJSON :: Value -> Parser SourceBreakpoint
parseJSON = Value -> Parser SourceBreakpoint
forall a.
(Generic a, GFromJSON Zero (Rep a), Typeable a) =>
Value -> Parser a
genericParseJSONWithModifier
data SetFunctionBreakpointsArguments
  = SetFunctionBreakpointsArguments
  { SetFunctionBreakpointsArguments -> [FunctionBreakpoint]
setFunctionBreakpointsArgumentsBreakpoints :: [FunctionBreakpoint]
    
    
    
  } deriving stock (Int -> SetFunctionBreakpointsArguments -> ShowS
[SetFunctionBreakpointsArguments] -> ShowS
SetFunctionBreakpointsArguments -> String
(Int -> SetFunctionBreakpointsArguments -> ShowS)
-> (SetFunctionBreakpointsArguments -> String)
-> ([SetFunctionBreakpointsArguments] -> ShowS)
-> Show SetFunctionBreakpointsArguments
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SetFunctionBreakpointsArguments -> ShowS
showsPrec :: Int -> SetFunctionBreakpointsArguments -> ShowS
$cshow :: SetFunctionBreakpointsArguments -> String
show :: SetFunctionBreakpointsArguments -> String
$cshowList :: [SetFunctionBreakpointsArguments] -> ShowS
showList :: [SetFunctionBreakpointsArguments] -> ShowS
Show, SetFunctionBreakpointsArguments
-> SetFunctionBreakpointsArguments -> Bool
(SetFunctionBreakpointsArguments
 -> SetFunctionBreakpointsArguments -> Bool)
-> (SetFunctionBreakpointsArguments
    -> SetFunctionBreakpointsArguments -> Bool)
-> Eq SetFunctionBreakpointsArguments
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SetFunctionBreakpointsArguments
-> SetFunctionBreakpointsArguments -> Bool
== :: SetFunctionBreakpointsArguments
-> SetFunctionBreakpointsArguments -> Bool
$c/= :: SetFunctionBreakpointsArguments
-> SetFunctionBreakpointsArguments -> Bool
/= :: SetFunctionBreakpointsArguments
-> SetFunctionBreakpointsArguments -> Bool
Eq, (forall x.
 SetFunctionBreakpointsArguments
 -> Rep SetFunctionBreakpointsArguments x)
-> (forall x.
    Rep SetFunctionBreakpointsArguments x
    -> SetFunctionBreakpointsArguments)
-> Generic SetFunctionBreakpointsArguments
forall x.
Rep SetFunctionBreakpointsArguments x
-> SetFunctionBreakpointsArguments
forall x.
SetFunctionBreakpointsArguments
-> Rep SetFunctionBreakpointsArguments x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x.
SetFunctionBreakpointsArguments
-> Rep SetFunctionBreakpointsArguments x
from :: forall x.
SetFunctionBreakpointsArguments
-> Rep SetFunctionBreakpointsArguments x
$cto :: forall x.
Rep SetFunctionBreakpointsArguments x
-> SetFunctionBreakpointsArguments
to :: forall x.
Rep SetFunctionBreakpointsArguments x
-> SetFunctionBreakpointsArguments
Generic)
instance FromJSON SetFunctionBreakpointsArguments where
  parseJSON :: Value -> Parser SetFunctionBreakpointsArguments
parseJSON = Value -> Parser SetFunctionBreakpointsArguments
forall a.
(Generic a, GFromJSON Zero (Rep a), Typeable a) =>
Value -> Parser a
genericParseJSONWithModifier
data FunctionBreakpoint
  = FunctionBreakpoint
  { FunctionBreakpoint -> Maybe Text
functionBreakpointName :: Maybe Text
    
    
    
  , FunctionBreakpoint -> Maybe Text
functionBreakpointCondition :: Maybe Text
    
    
    
    
    
  , FunctionBreakpoint -> Maybe Text
functionBreakpointHitCondition :: Maybe Text
    
    
    
    
    
    
  } deriving stock (Int -> FunctionBreakpoint -> ShowS
[FunctionBreakpoint] -> ShowS
FunctionBreakpoint -> String
(Int -> FunctionBreakpoint -> ShowS)
-> (FunctionBreakpoint -> String)
-> ([FunctionBreakpoint] -> ShowS)
-> Show FunctionBreakpoint
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> FunctionBreakpoint -> ShowS
showsPrec :: Int -> FunctionBreakpoint -> ShowS
$cshow :: FunctionBreakpoint -> String
show :: FunctionBreakpoint -> String
$cshowList :: [FunctionBreakpoint] -> ShowS
showList :: [FunctionBreakpoint] -> ShowS
Show, FunctionBreakpoint -> FunctionBreakpoint -> Bool
(FunctionBreakpoint -> FunctionBreakpoint -> Bool)
-> (FunctionBreakpoint -> FunctionBreakpoint -> Bool)
-> Eq FunctionBreakpoint
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FunctionBreakpoint -> FunctionBreakpoint -> Bool
== :: FunctionBreakpoint -> FunctionBreakpoint -> Bool
$c/= :: FunctionBreakpoint -> FunctionBreakpoint -> Bool
/= :: FunctionBreakpoint -> FunctionBreakpoint -> Bool
Eq, (forall x. FunctionBreakpoint -> Rep FunctionBreakpoint x)
-> (forall x. Rep FunctionBreakpoint x -> FunctionBreakpoint)
-> Generic FunctionBreakpoint
forall x. Rep FunctionBreakpoint x -> FunctionBreakpoint
forall x. FunctionBreakpoint -> Rep FunctionBreakpoint x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. FunctionBreakpoint -> Rep FunctionBreakpoint x
from :: forall x. FunctionBreakpoint -> Rep FunctionBreakpoint x
$cto :: forall x. Rep FunctionBreakpoint x -> FunctionBreakpoint
to :: forall x. Rep FunctionBreakpoint x -> FunctionBreakpoint
Generic)
defaultFunctionBreakpoint :: FunctionBreakpoint
defaultFunctionBreakpoint :: FunctionBreakpoint
defaultFunctionBreakpoint
  = FunctionBreakpoint
  { functionBreakpointName :: Maybe Text
functionBreakpointName = Maybe Text
forall a. Maybe a
Nothing
  , functionBreakpointCondition :: Maybe Text
functionBreakpointCondition = Maybe Text
forall a. Maybe a
Nothing
  , functionBreakpointHitCondition :: Maybe Text
functionBreakpointHitCondition = Maybe Text
forall a. Maybe a
Nothing
  }
instance FromJSON FunctionBreakpoint where
  parseJSON :: Value -> Parser FunctionBreakpoint
parseJSON = Value -> Parser FunctionBreakpoint
forall a.
(Generic a, GFromJSON Zero (Rep a), Typeable a) =>
Value -> Parser a
genericParseJSONWithModifier
data SetExceptionBreakpointsArguments
  = SetExceptionBreakpointsArguments
  { SetExceptionBreakpointsArguments -> [Text]
setExceptionBreakpointsArgumentsFilters :: [Text]
    
    
    
    
    
  , SetExceptionBreakpointsArguments -> Maybe ExceptionFilterOptions
setExceptionBreakpointsArgumentsFilterOptions :: Maybe ExceptionFilterOptions 
    
    
    
    
    
    
    
  , SetExceptionBreakpointsArguments -> Maybe ExceptionOptions
setExceptionBreakpointsArgumentsExceptionOptions :: Maybe ExceptionOptions
   
   
   
   
   
  } deriving stock (Int -> SetExceptionBreakpointsArguments -> ShowS
[SetExceptionBreakpointsArguments] -> ShowS
SetExceptionBreakpointsArguments -> String
(Int -> SetExceptionBreakpointsArguments -> ShowS)
-> (SetExceptionBreakpointsArguments -> String)
-> ([SetExceptionBreakpointsArguments] -> ShowS)
-> Show SetExceptionBreakpointsArguments
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SetExceptionBreakpointsArguments -> ShowS
showsPrec :: Int -> SetExceptionBreakpointsArguments -> ShowS
$cshow :: SetExceptionBreakpointsArguments -> String
show :: SetExceptionBreakpointsArguments -> String
$cshowList :: [SetExceptionBreakpointsArguments] -> ShowS
showList :: [SetExceptionBreakpointsArguments] -> ShowS
Show, SetExceptionBreakpointsArguments
-> SetExceptionBreakpointsArguments -> Bool
(SetExceptionBreakpointsArguments
 -> SetExceptionBreakpointsArguments -> Bool)
-> (SetExceptionBreakpointsArguments
    -> SetExceptionBreakpointsArguments -> Bool)
-> Eq SetExceptionBreakpointsArguments
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SetExceptionBreakpointsArguments
-> SetExceptionBreakpointsArguments -> Bool
== :: SetExceptionBreakpointsArguments
-> SetExceptionBreakpointsArguments -> Bool
$c/= :: SetExceptionBreakpointsArguments
-> SetExceptionBreakpointsArguments -> Bool
/= :: SetExceptionBreakpointsArguments
-> SetExceptionBreakpointsArguments -> Bool
Eq, (forall x.
 SetExceptionBreakpointsArguments
 -> Rep SetExceptionBreakpointsArguments x)
-> (forall x.
    Rep SetExceptionBreakpointsArguments x
    -> SetExceptionBreakpointsArguments)
-> Generic SetExceptionBreakpointsArguments
forall x.
Rep SetExceptionBreakpointsArguments x
-> SetExceptionBreakpointsArguments
forall x.
SetExceptionBreakpointsArguments
-> Rep SetExceptionBreakpointsArguments x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x.
SetExceptionBreakpointsArguments
-> Rep SetExceptionBreakpointsArguments x
from :: forall x.
SetExceptionBreakpointsArguments
-> Rep SetExceptionBreakpointsArguments x
$cto :: forall x.
Rep SetExceptionBreakpointsArguments x
-> SetExceptionBreakpointsArguments
to :: forall x.
Rep SetExceptionBreakpointsArguments x
-> SetExceptionBreakpointsArguments
Generic)
instance FromJSON SetExceptionBreakpointsArguments where
  parseJSON :: Value -> Parser SetExceptionBreakpointsArguments
parseJSON = Value -> Parser SetExceptionBreakpointsArguments
forall a.
(Generic a, GFromJSON Zero (Rep a), Typeable a) =>
Value -> Parser a
genericParseJSONWithModifier
data ExceptionFilterOptions
  = ExceptionFilterOptions
  { ExceptionFilterOptions -> String
exceptionFilterOptionsFilterId :: String
    
    
  , ExceptionFilterOptions -> Maybe String
exceptionFilterOptionsCondition :: Maybe String
    
    
    
  } deriving stock (Int -> ExceptionFilterOptions -> ShowS
[ExceptionFilterOptions] -> ShowS
ExceptionFilterOptions -> String
(Int -> ExceptionFilterOptions -> ShowS)
-> (ExceptionFilterOptions -> String)
-> ([ExceptionFilterOptions] -> ShowS)
-> Show ExceptionFilterOptions
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ExceptionFilterOptions -> ShowS
showsPrec :: Int -> ExceptionFilterOptions -> ShowS
$cshow :: ExceptionFilterOptions -> String
show :: ExceptionFilterOptions -> String
$cshowList :: [ExceptionFilterOptions] -> ShowS
showList :: [ExceptionFilterOptions] -> ShowS
Show, ExceptionFilterOptions -> ExceptionFilterOptions -> Bool
(ExceptionFilterOptions -> ExceptionFilterOptions -> Bool)
-> (ExceptionFilterOptions -> ExceptionFilterOptions -> Bool)
-> Eq ExceptionFilterOptions
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ExceptionFilterOptions -> ExceptionFilterOptions -> Bool
== :: ExceptionFilterOptions -> ExceptionFilterOptions -> Bool
$c/= :: ExceptionFilterOptions -> ExceptionFilterOptions -> Bool
/= :: ExceptionFilterOptions -> ExceptionFilterOptions -> Bool
Eq, (forall x. ExceptionFilterOptions -> Rep ExceptionFilterOptions x)
-> (forall x.
    Rep ExceptionFilterOptions x -> ExceptionFilterOptions)
-> Generic ExceptionFilterOptions
forall x. Rep ExceptionFilterOptions x -> ExceptionFilterOptions
forall x. ExceptionFilterOptions -> Rep ExceptionFilterOptions x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ExceptionFilterOptions -> Rep ExceptionFilterOptions x
from :: forall x. ExceptionFilterOptions -> Rep ExceptionFilterOptions x
$cto :: forall x. Rep ExceptionFilterOptions x -> ExceptionFilterOptions
to :: forall x. Rep ExceptionFilterOptions x -> ExceptionFilterOptions
Generic)
instance FromJSON ExceptionFilterOptions where
  parseJSON :: Value -> Parser ExceptionFilterOptions
parseJSON = Value -> Parser ExceptionFilterOptions
forall a.
(Generic a, GFromJSON Zero (Rep a), Typeable a) =>
Value -> Parser a
genericParseJSONWithModifier
data ExceptionOptions
  = ExceptionOptions
  { ExceptionOptions -> Maybe [ExceptionPathSegment]
exceptionOptionsPath :: Maybe [ExceptionPathSegment]
    
    
    
    
    
    
  , ExceptionOptions -> ExceptionBreakMode
exceptionOptionsBreakMode :: ExceptionBreakMode
    
    
    
  } deriving stock (Int -> ExceptionOptions -> ShowS
[ExceptionOptions] -> ShowS
ExceptionOptions -> String
(Int -> ExceptionOptions -> ShowS)
-> (ExceptionOptions -> String)
-> ([ExceptionOptions] -> ShowS)
-> Show ExceptionOptions
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ExceptionOptions -> ShowS
showsPrec :: Int -> ExceptionOptions -> ShowS
$cshow :: ExceptionOptions -> String
show :: ExceptionOptions -> String
$cshowList :: [ExceptionOptions] -> ShowS
showList :: [ExceptionOptions] -> ShowS
Show, ExceptionOptions -> ExceptionOptions -> Bool
(ExceptionOptions -> ExceptionOptions -> Bool)
-> (ExceptionOptions -> ExceptionOptions -> Bool)
-> Eq ExceptionOptions
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ExceptionOptions -> ExceptionOptions -> Bool
== :: ExceptionOptions -> ExceptionOptions -> Bool
$c/= :: ExceptionOptions -> ExceptionOptions -> Bool
/= :: ExceptionOptions -> ExceptionOptions -> Bool
Eq, (forall x. ExceptionOptions -> Rep ExceptionOptions x)
-> (forall x. Rep ExceptionOptions x -> ExceptionOptions)
-> Generic ExceptionOptions
forall x. Rep ExceptionOptions x -> ExceptionOptions
forall x. ExceptionOptions -> Rep ExceptionOptions x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ExceptionOptions -> Rep ExceptionOptions x
from :: forall x. ExceptionOptions -> Rep ExceptionOptions x
$cto :: forall x. Rep ExceptionOptions x -> ExceptionOptions
to :: forall x. Rep ExceptionOptions x -> ExceptionOptions
Generic)
instance FromJSON ExceptionOptions where
  parseJSON :: Value -> Parser ExceptionOptions
parseJSON = Value -> Parser ExceptionOptions
forall a.
(Generic a, GFromJSON Zero (Rep a), Typeable a) =>
Value -> Parser a
genericParseJSONWithModifier
data DataBreakpointInfoArguments
  = DataBreakpointInfoArguments
  { DataBreakpointInfoArguments -> Maybe Int
dataBreakpointInfoArgumentsVariablesReference :: Maybe Int
    
    
    
    
    
    
  , DataBreakpointInfoArguments -> Text
dataBreakpointInfoArgumentsName :: Text
    
    
    
    
  , DataBreakpointInfoArguments -> Maybe Int
dataBreakpointInfoArgumentsFrameId :: Maybe Int
    
    
    
    
    
  } deriving stock (Int -> DataBreakpointInfoArguments -> ShowS
[DataBreakpointInfoArguments] -> ShowS
DataBreakpointInfoArguments -> String
(Int -> DataBreakpointInfoArguments -> ShowS)
-> (DataBreakpointInfoArguments -> String)
-> ([DataBreakpointInfoArguments] -> ShowS)
-> Show DataBreakpointInfoArguments
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> DataBreakpointInfoArguments -> ShowS
showsPrec :: Int -> DataBreakpointInfoArguments -> ShowS
$cshow :: DataBreakpointInfoArguments -> String
show :: DataBreakpointInfoArguments -> String
$cshowList :: [DataBreakpointInfoArguments] -> ShowS
showList :: [DataBreakpointInfoArguments] -> ShowS
Show, DataBreakpointInfoArguments -> DataBreakpointInfoArguments -> Bool
(DataBreakpointInfoArguments
 -> DataBreakpointInfoArguments -> Bool)
-> (DataBreakpointInfoArguments
    -> DataBreakpointInfoArguments -> Bool)
-> Eq DataBreakpointInfoArguments
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DataBreakpointInfoArguments -> DataBreakpointInfoArguments -> Bool
== :: DataBreakpointInfoArguments -> DataBreakpointInfoArguments -> Bool
$c/= :: DataBreakpointInfoArguments -> DataBreakpointInfoArguments -> Bool
/= :: DataBreakpointInfoArguments -> DataBreakpointInfoArguments -> Bool
Eq, (forall x.
 DataBreakpointInfoArguments -> Rep DataBreakpointInfoArguments x)
-> (forall x.
    Rep DataBreakpointInfoArguments x -> DataBreakpointInfoArguments)
-> Generic DataBreakpointInfoArguments
forall x.
Rep DataBreakpointInfoArguments x -> DataBreakpointInfoArguments
forall x.
DataBreakpointInfoArguments -> Rep DataBreakpointInfoArguments x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x.
DataBreakpointInfoArguments -> Rep DataBreakpointInfoArguments x
from :: forall x.
DataBreakpointInfoArguments -> Rep DataBreakpointInfoArguments x
$cto :: forall x.
Rep DataBreakpointInfoArguments x -> DataBreakpointInfoArguments
to :: forall x.
Rep DataBreakpointInfoArguments x -> DataBreakpointInfoArguments
Generic)
instance FromJSON DataBreakpointInfoArguments where
  parseJSON :: Value -> Parser DataBreakpointInfoArguments
parseJSON = Value -> Parser DataBreakpointInfoArguments
forall a.
(Generic a, GFromJSON Zero (Rep a), Typeable a) =>
Value -> Parser a
genericParseJSONWithModifier
data SetDataBreakpointsArguments
  = SetDataBreakpointsArguments
  { SetDataBreakpointsArguments -> [DataBreakpoint]
setDataBreakpointsArgumentsBreakpoints :: [DataBreakpoint]
    
    
    
    
  } deriving stock (Int -> SetDataBreakpointsArguments -> ShowS
[SetDataBreakpointsArguments] -> ShowS
SetDataBreakpointsArguments -> String
(Int -> SetDataBreakpointsArguments -> ShowS)
-> (SetDataBreakpointsArguments -> String)
-> ([SetDataBreakpointsArguments] -> ShowS)
-> Show SetDataBreakpointsArguments
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SetDataBreakpointsArguments -> ShowS
showsPrec :: Int -> SetDataBreakpointsArguments -> ShowS
$cshow :: SetDataBreakpointsArguments -> String
show :: SetDataBreakpointsArguments -> String
$cshowList :: [SetDataBreakpointsArguments] -> ShowS
showList :: [SetDataBreakpointsArguments] -> ShowS
Show, SetDataBreakpointsArguments -> SetDataBreakpointsArguments -> Bool
(SetDataBreakpointsArguments
 -> SetDataBreakpointsArguments -> Bool)
-> (SetDataBreakpointsArguments
    -> SetDataBreakpointsArguments -> Bool)
-> Eq SetDataBreakpointsArguments
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SetDataBreakpointsArguments -> SetDataBreakpointsArguments -> Bool
== :: SetDataBreakpointsArguments -> SetDataBreakpointsArguments -> Bool
$c/= :: SetDataBreakpointsArguments -> SetDataBreakpointsArguments -> Bool
/= :: SetDataBreakpointsArguments -> SetDataBreakpointsArguments -> Bool
Eq, (forall x.
 SetDataBreakpointsArguments -> Rep SetDataBreakpointsArguments x)
-> (forall x.
    Rep SetDataBreakpointsArguments x -> SetDataBreakpointsArguments)
-> Generic SetDataBreakpointsArguments
forall x.
Rep SetDataBreakpointsArguments x -> SetDataBreakpointsArguments
forall x.
SetDataBreakpointsArguments -> Rep SetDataBreakpointsArguments x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x.
SetDataBreakpointsArguments -> Rep SetDataBreakpointsArguments x
from :: forall x.
SetDataBreakpointsArguments -> Rep SetDataBreakpointsArguments x
$cto :: forall x.
Rep SetDataBreakpointsArguments x -> SetDataBreakpointsArguments
to :: forall x.
Rep SetDataBreakpointsArguments x -> SetDataBreakpointsArguments
Generic)
instance FromJSON SetDataBreakpointsArguments where
  parseJSON :: Value -> Parser SetDataBreakpointsArguments
parseJSON = Value -> Parser SetDataBreakpointsArguments
forall a.
(Generic a, GFromJSON Zero (Rep a), Typeable a) =>
Value -> Parser a
genericParseJSONWithModifier
data DataBreakpoint
  = DataBreakpoint
  { DataBreakpoint -> Text
dataBreakpointDataId :: Text
    
    
    
    
  , DataBreakpoint -> Maybe DataBreakpointAccessType
dataBreakpointAccessType :: Maybe DataBreakpointAccessType
    
    
    
  , DataBreakpoint -> Maybe Text
condition :: Maybe Text
    
    
    
  , DataBreakpoint -> Maybe Text
hitCondition :: Maybe Text
    
    
    
    
  } deriving stock (Int -> DataBreakpoint -> ShowS
[DataBreakpoint] -> ShowS
DataBreakpoint -> String
(Int -> DataBreakpoint -> ShowS)
-> (DataBreakpoint -> String)
-> ([DataBreakpoint] -> ShowS)
-> Show DataBreakpoint
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> DataBreakpoint -> ShowS
showsPrec :: Int -> DataBreakpoint -> ShowS
$cshow :: DataBreakpoint -> String
show :: DataBreakpoint -> String
$cshowList :: [DataBreakpoint] -> ShowS
showList :: [DataBreakpoint] -> ShowS
Show, DataBreakpoint -> DataBreakpoint -> Bool
(DataBreakpoint -> DataBreakpoint -> Bool)
-> (DataBreakpoint -> DataBreakpoint -> Bool) -> Eq DataBreakpoint
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DataBreakpoint -> DataBreakpoint -> Bool
== :: DataBreakpoint -> DataBreakpoint -> Bool
$c/= :: DataBreakpoint -> DataBreakpoint -> Bool
/= :: DataBreakpoint -> DataBreakpoint -> Bool
Eq, (forall x. DataBreakpoint -> Rep DataBreakpoint x)
-> (forall x. Rep DataBreakpoint x -> DataBreakpoint)
-> Generic DataBreakpoint
forall x. Rep DataBreakpoint x -> DataBreakpoint
forall x. DataBreakpoint -> Rep DataBreakpoint x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. DataBreakpoint -> Rep DataBreakpoint x
from :: forall x. DataBreakpoint -> Rep DataBreakpoint x
$cto :: forall x. Rep DataBreakpoint x -> DataBreakpoint
to :: forall x. Rep DataBreakpoint x -> DataBreakpoint
Generic)
instance FromJSON DataBreakpoint where
  parseJSON :: Value -> Parser DataBreakpoint
parseJSON = Value -> Parser DataBreakpoint
forall a.
(Generic a, GFromJSON Zero (Rep a), Typeable a) =>
Value -> Parser a
genericParseJSONWithModifier
data SetInstructionBreakpointsArguments
  = SetInstructionBreakpointsArguments
  { SetInstructionBreakpointsArguments -> [InstructionBreakpoint]
breakpoints :: [InstructionBreakpoint]
    
    
    
  } deriving (Int -> SetInstructionBreakpointsArguments -> ShowS
[SetInstructionBreakpointsArguments] -> ShowS
SetInstructionBreakpointsArguments -> String
(Int -> SetInstructionBreakpointsArguments -> ShowS)
-> (SetInstructionBreakpointsArguments -> String)
-> ([SetInstructionBreakpointsArguments] -> ShowS)
-> Show SetInstructionBreakpointsArguments
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SetInstructionBreakpointsArguments -> ShowS
showsPrec :: Int -> SetInstructionBreakpointsArguments -> ShowS
$cshow :: SetInstructionBreakpointsArguments -> String
show :: SetInstructionBreakpointsArguments -> String
$cshowList :: [SetInstructionBreakpointsArguments] -> ShowS
showList :: [SetInstructionBreakpointsArguments] -> ShowS
Show, SetInstructionBreakpointsArguments
-> SetInstructionBreakpointsArguments -> Bool
(SetInstructionBreakpointsArguments
 -> SetInstructionBreakpointsArguments -> Bool)
-> (SetInstructionBreakpointsArguments
    -> SetInstructionBreakpointsArguments -> Bool)
-> Eq SetInstructionBreakpointsArguments
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SetInstructionBreakpointsArguments
-> SetInstructionBreakpointsArguments -> Bool
== :: SetInstructionBreakpointsArguments
-> SetInstructionBreakpointsArguments -> Bool
$c/= :: SetInstructionBreakpointsArguments
-> SetInstructionBreakpointsArguments -> Bool
/= :: SetInstructionBreakpointsArguments
-> SetInstructionBreakpointsArguments -> Bool
Eq)
data InstructionBreakpoint
  = InstructionBreakpoint
  { InstructionBreakpoint -> Text
instructionBreakpointInstructionReference :: Text
    
    
    
    
    
    
  , InstructionBreakpoint -> Maybe Int
instructionBreakpointOffset :: Maybe Int
    
    
    
    
  , InstructionBreakpoint -> Maybe Text
instructionBreakpointCondition :: Maybe Text
    
    
    
    
    
  , InstructionBreakpoint -> Maybe Text
instructionBreakpointHitCondition :: Maybe Text
    
    
    
    
    
    
  } deriving stock (Int -> InstructionBreakpoint -> ShowS
[InstructionBreakpoint] -> ShowS
InstructionBreakpoint -> String
(Int -> InstructionBreakpoint -> ShowS)
-> (InstructionBreakpoint -> String)
-> ([InstructionBreakpoint] -> ShowS)
-> Show InstructionBreakpoint
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> InstructionBreakpoint -> ShowS
showsPrec :: Int -> InstructionBreakpoint -> ShowS
$cshow :: InstructionBreakpoint -> String
show :: InstructionBreakpoint -> String
$cshowList :: [InstructionBreakpoint] -> ShowS
showList :: [InstructionBreakpoint] -> ShowS
Show, InstructionBreakpoint -> InstructionBreakpoint -> Bool
(InstructionBreakpoint -> InstructionBreakpoint -> Bool)
-> (InstructionBreakpoint -> InstructionBreakpoint -> Bool)
-> Eq InstructionBreakpoint
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: InstructionBreakpoint -> InstructionBreakpoint -> Bool
== :: InstructionBreakpoint -> InstructionBreakpoint -> Bool
$c/= :: InstructionBreakpoint -> InstructionBreakpoint -> Bool
/= :: InstructionBreakpoint -> InstructionBreakpoint -> Bool
Eq, (forall x. InstructionBreakpoint -> Rep InstructionBreakpoint x)
-> (forall x. Rep InstructionBreakpoint x -> InstructionBreakpoint)
-> Generic InstructionBreakpoint
forall x. Rep InstructionBreakpoint x -> InstructionBreakpoint
forall x. InstructionBreakpoint -> Rep InstructionBreakpoint x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. InstructionBreakpoint -> Rep InstructionBreakpoint x
from :: forall x. InstructionBreakpoint -> Rep InstructionBreakpoint x
$cto :: forall x. Rep InstructionBreakpoint x -> InstructionBreakpoint
to :: forall x. Rep InstructionBreakpoint x -> InstructionBreakpoint
Generic)
instance FromJSON InstructionBreakpoint where
  parseJSON :: Value -> Parser InstructionBreakpoint
parseJSON = Value -> Parser InstructionBreakpoint
forall a.
(Generic a, GFromJSON Zero (Rep a), Typeable a) =>
Value -> Parser a
genericParseJSONWithModifier
data ContinueArguments
  = ContinueArguments
  { ContinueArguments -> Int
continueArgumentsThreadId :: Int
    
    
    
    
    
  , ContinueArguments -> Bool
continueArgumentsSingleThread :: Bool
    
    
    
    
  } deriving stock (Int -> ContinueArguments -> ShowS
[ContinueArguments] -> ShowS
ContinueArguments -> String
(Int -> ContinueArguments -> ShowS)
-> (ContinueArguments -> String)
-> ([ContinueArguments] -> ShowS)
-> Show ContinueArguments
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ContinueArguments -> ShowS
showsPrec :: Int -> ContinueArguments -> ShowS
$cshow :: ContinueArguments -> String
show :: ContinueArguments -> String
$cshowList :: [ContinueArguments] -> ShowS
showList :: [ContinueArguments] -> ShowS
Show, ContinueArguments -> ContinueArguments -> Bool
(ContinueArguments -> ContinueArguments -> Bool)
-> (ContinueArguments -> ContinueArguments -> Bool)
-> Eq ContinueArguments
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ContinueArguments -> ContinueArguments -> Bool
== :: ContinueArguments -> ContinueArguments -> Bool
$c/= :: ContinueArguments -> ContinueArguments -> Bool
/= :: ContinueArguments -> ContinueArguments -> Bool
Eq, (forall x. ContinueArguments -> Rep ContinueArguments x)
-> (forall x. Rep ContinueArguments x -> ContinueArguments)
-> Generic ContinueArguments
forall x. Rep ContinueArguments x -> ContinueArguments
forall x. ContinueArguments -> Rep ContinueArguments x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ContinueArguments -> Rep ContinueArguments x
from :: forall x. ContinueArguments -> Rep ContinueArguments x
$cto :: forall x. Rep ContinueArguments x -> ContinueArguments
to :: forall x. Rep ContinueArguments x -> ContinueArguments
Generic)
instance FromJSON ContinueArguments where
  parseJSON :: Value -> Parser ContinueArguments
parseJSON = Value -> Parser ContinueArguments
forall a.
(Generic a, GFromJSON Zero (Rep a), Typeable a) =>
Value -> Parser a
genericParseJSONWithModifier
data NextArguments
  = NextArguments
  { NextArguments -> Int
nextArgumentsThreadId :: Int
   
   
   
   
  , NextArguments -> Maybe Bool
nextArgumentsSingleThread :: Maybe Bool
   
   
   
  , NextArguments -> Maybe SteppingGranularity
nextArgumentsGranularity :: Maybe SteppingGranularity
   
   
   
   
  } deriving stock (Int -> NextArguments -> ShowS
[NextArguments] -> ShowS
NextArguments -> String
(Int -> NextArguments -> ShowS)
-> (NextArguments -> String)
-> ([NextArguments] -> ShowS)
-> Show NextArguments
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> NextArguments -> ShowS
showsPrec :: Int -> NextArguments -> ShowS
$cshow :: NextArguments -> String
show :: NextArguments -> String
$cshowList :: [NextArguments] -> ShowS
showList :: [NextArguments] -> ShowS
Show, NextArguments -> NextArguments -> Bool
(NextArguments -> NextArguments -> Bool)
-> (NextArguments -> NextArguments -> Bool) -> Eq NextArguments
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: NextArguments -> NextArguments -> Bool
== :: NextArguments -> NextArguments -> Bool
$c/= :: NextArguments -> NextArguments -> Bool
/= :: NextArguments -> NextArguments -> Bool
Eq, (forall x. NextArguments -> Rep NextArguments x)
-> (forall x. Rep NextArguments x -> NextArguments)
-> Generic NextArguments
forall x. Rep NextArguments x -> NextArguments
forall x. NextArguments -> Rep NextArguments x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. NextArguments -> Rep NextArguments x
from :: forall x. NextArguments -> Rep NextArguments x
$cto :: forall x. Rep NextArguments x -> NextArguments
to :: forall x. Rep NextArguments x -> NextArguments
Generic)
instance FromJSON NextArguments where
  parseJSON :: Value -> Parser NextArguments
parseJSON = Value -> Parser NextArguments
forall a.
(Generic a, GFromJSON Zero (Rep a), Typeable a) =>
Value -> Parser a
genericParseJSONWithModifier
data StepInArguments
  = StepInArguments
  { StepInArguments -> Int
stepInArgumentsThreadId :: Int
    
    
    
    
  , StepInArguments -> Bool
stepInArgumentsSingleThread :: Bool
    
    
    
  , StepInArguments -> Maybe Int
stepInArgumentsTargetId :: Maybe Int
    
    
    
  , StepInArguments -> Maybe SteppingGranularity
stepInArgumentsGranularity :: Maybe SteppingGranularity
    
    
    
    
  } deriving stock (Int -> StepInArguments -> ShowS
[StepInArguments] -> ShowS
StepInArguments -> String
(Int -> StepInArguments -> ShowS)
-> (StepInArguments -> String)
-> ([StepInArguments] -> ShowS)
-> Show StepInArguments
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> StepInArguments -> ShowS
showsPrec :: Int -> StepInArguments -> ShowS
$cshow :: StepInArguments -> String
show :: StepInArguments -> String
$cshowList :: [StepInArguments] -> ShowS
showList :: [StepInArguments] -> ShowS
Show, StepInArguments -> StepInArguments -> Bool
(StepInArguments -> StepInArguments -> Bool)
-> (StepInArguments -> StepInArguments -> Bool)
-> Eq StepInArguments
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: StepInArguments -> StepInArguments -> Bool
== :: StepInArguments -> StepInArguments -> Bool
$c/= :: StepInArguments -> StepInArguments -> Bool
/= :: StepInArguments -> StepInArguments -> Bool
Eq)
data StepOutArguments
  = StepOutArguments
  { StepOutArguments -> Int
stepOutArgumentsThreadId :: Int
    
    
    
    
  , StepOutArguments -> Bool
stepOutArgumentsSingleThread :: Bool
    
    
    
  , StepOutArguments -> Maybe SteppingGranularity
stepOutArgumentsGranularity :: Maybe SteppingGranularity
    
    
    
    
  } deriving stock (Int -> StepOutArguments -> ShowS
[StepOutArguments] -> ShowS
StepOutArguments -> String
(Int -> StepOutArguments -> ShowS)
-> (StepOutArguments -> String)
-> ([StepOutArguments] -> ShowS)
-> Show StepOutArguments
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> StepOutArguments -> ShowS
showsPrec :: Int -> StepOutArguments -> ShowS
$cshow :: StepOutArguments -> String
show :: StepOutArguments -> String
$cshowList :: [StepOutArguments] -> ShowS
showList :: [StepOutArguments] -> ShowS
Show, StepOutArguments -> StepOutArguments -> Bool
(StepOutArguments -> StepOutArguments -> Bool)
-> (StepOutArguments -> StepOutArguments -> Bool)
-> Eq StepOutArguments
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: StepOutArguments -> StepOutArguments -> Bool
== :: StepOutArguments -> StepOutArguments -> Bool
$c/= :: StepOutArguments -> StepOutArguments -> Bool
/= :: StepOutArguments -> StepOutArguments -> Bool
Eq)
data StepBackArguments
  = StepBackArguments
  { StepBackArguments -> Int
stepBackArgumentsThreadId :: Int
    
    
    
    
  , StepBackArguments -> Bool
stepBackArgumentsSingleThread :: Bool
    
    
    
  , StepBackArguments -> Maybe SteppingGranularity
stepBackArgumentsGranularity :: Maybe SteppingGranularity
    
    
    
  } deriving stock (Int -> StepBackArguments -> ShowS
[StepBackArguments] -> ShowS
StepBackArguments -> String
(Int -> StepBackArguments -> ShowS)
-> (StepBackArguments -> String)
-> ([StepBackArguments] -> ShowS)
-> Show StepBackArguments
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> StepBackArguments -> ShowS
showsPrec :: Int -> StepBackArguments -> ShowS
$cshow :: StepBackArguments -> String
show :: StepBackArguments -> String
$cshowList :: [StepBackArguments] -> ShowS
showList :: [StepBackArguments] -> ShowS
Show, StepBackArguments -> StepBackArguments -> Bool
(StepBackArguments -> StepBackArguments -> Bool)
-> (StepBackArguments -> StepBackArguments -> Bool)
-> Eq StepBackArguments
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: StepBackArguments -> StepBackArguments -> Bool
== :: StepBackArguments -> StepBackArguments -> Bool
$c/= :: StepBackArguments -> StepBackArguments -> Bool
/= :: StepBackArguments -> StepBackArguments -> Bool
Eq)
data SteppingGranularity
  = SteppingGranularityStatement
  | SteppingGranularityLine
  | SteppingGranularityInstruction
  deriving stock (Int -> SteppingGranularity -> ShowS
[SteppingGranularity] -> ShowS
SteppingGranularity -> String
(Int -> SteppingGranularity -> ShowS)
-> (SteppingGranularity -> String)
-> ([SteppingGranularity] -> ShowS)
-> Show SteppingGranularity
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SteppingGranularity -> ShowS
showsPrec :: Int -> SteppingGranularity -> ShowS
$cshow :: SteppingGranularity -> String
show :: SteppingGranularity -> String
$cshowList :: [SteppingGranularity] -> ShowS
showList :: [SteppingGranularity] -> ShowS
Show, SteppingGranularity -> SteppingGranularity -> Bool
(SteppingGranularity -> SteppingGranularity -> Bool)
-> (SteppingGranularity -> SteppingGranularity -> Bool)
-> Eq SteppingGranularity
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SteppingGranularity -> SteppingGranularity -> Bool
== :: SteppingGranularity -> SteppingGranularity -> Bool
$c/= :: SteppingGranularity -> SteppingGranularity -> Bool
/= :: SteppingGranularity -> SteppingGranularity -> Bool
Eq, (forall x. SteppingGranularity -> Rep SteppingGranularity x)
-> (forall x. Rep SteppingGranularity x -> SteppingGranularity)
-> Generic SteppingGranularity
forall x. Rep SteppingGranularity x -> SteppingGranularity
forall x. SteppingGranularity -> Rep SteppingGranularity x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. SteppingGranularity -> Rep SteppingGranularity x
from :: forall x. SteppingGranularity -> Rep SteppingGranularity x
$cto :: forall x. Rep SteppingGranularity x -> SteppingGranularity
to :: forall x. Rep SteppingGranularity x -> SteppingGranularity
Generic)
instance FromJSON SteppingGranularity where
  parseJSON :: Value -> Parser SteppingGranularity
parseJSON = Value -> Parser SteppingGranularity
forall a.
(Generic a, GFromJSON Zero (Rep a), Typeable a) =>
Value -> Parser a
genericParseJSONWithModifier
data ReverseContinueArguments
  = ReverseContinueArguments
  { ReverseContinueArguments -> Int
reverseContinueArgumentsThreadId :: Int
   
   
   
   
   
  , ReverseContinueArguments -> Bool
reverseContinueArgumentsSingleThread :: Bool
   
   
   
   
  } deriving stock (Int -> ReverseContinueArguments -> ShowS
[ReverseContinueArguments] -> ShowS
ReverseContinueArguments -> String
(Int -> ReverseContinueArguments -> ShowS)
-> (ReverseContinueArguments -> String)
-> ([ReverseContinueArguments] -> ShowS)
-> Show ReverseContinueArguments
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ReverseContinueArguments -> ShowS
showsPrec :: Int -> ReverseContinueArguments -> ShowS
$cshow :: ReverseContinueArguments -> String
show :: ReverseContinueArguments -> String
$cshowList :: [ReverseContinueArguments] -> ShowS
showList :: [ReverseContinueArguments] -> ShowS
Show, ReverseContinueArguments -> ReverseContinueArguments -> Bool
(ReverseContinueArguments -> ReverseContinueArguments -> Bool)
-> (ReverseContinueArguments -> ReverseContinueArguments -> Bool)
-> Eq ReverseContinueArguments
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ReverseContinueArguments -> ReverseContinueArguments -> Bool
== :: ReverseContinueArguments -> ReverseContinueArguments -> Bool
$c/= :: ReverseContinueArguments -> ReverseContinueArguments -> Bool
/= :: ReverseContinueArguments -> ReverseContinueArguments -> Bool
Eq, (forall x.
 ReverseContinueArguments -> Rep ReverseContinueArguments x)
-> (forall x.
    Rep ReverseContinueArguments x -> ReverseContinueArguments)
-> Generic ReverseContinueArguments
forall x.
Rep ReverseContinueArguments x -> ReverseContinueArguments
forall x.
ReverseContinueArguments -> Rep ReverseContinueArguments x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x.
ReverseContinueArguments -> Rep ReverseContinueArguments x
from :: forall x.
ReverseContinueArguments -> Rep ReverseContinueArguments x
$cto :: forall x.
Rep ReverseContinueArguments x -> ReverseContinueArguments
to :: forall x.
Rep ReverseContinueArguments x -> ReverseContinueArguments
Generic)
instance FromJSON ReverseContinueArguments where
  parseJSON :: Value -> Parser ReverseContinueArguments
parseJSON = Value -> Parser ReverseContinueArguments
forall a.
(Generic a, GFromJSON Zero (Rep a), Typeable a) =>
Value -> Parser a
genericParseJSONWithModifier
data RestartFrameArguments
  = RestartFrameArguments
  { RestartFrameArguments -> Int
restartFrameArgumentsFrameId :: Int
   
   
   
   
   
  } deriving stock (Int -> RestartFrameArguments -> ShowS
[RestartFrameArguments] -> ShowS
RestartFrameArguments -> String
(Int -> RestartFrameArguments -> ShowS)
-> (RestartFrameArguments -> String)
-> ([RestartFrameArguments] -> ShowS)
-> Show RestartFrameArguments
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RestartFrameArguments -> ShowS
showsPrec :: Int -> RestartFrameArguments -> ShowS
$cshow :: RestartFrameArguments -> String
show :: RestartFrameArguments -> String
$cshowList :: [RestartFrameArguments] -> ShowS
showList :: [RestartFrameArguments] -> ShowS
Show, RestartFrameArguments -> RestartFrameArguments -> Bool
(RestartFrameArguments -> RestartFrameArguments -> Bool)
-> (RestartFrameArguments -> RestartFrameArguments -> Bool)
-> Eq RestartFrameArguments
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RestartFrameArguments -> RestartFrameArguments -> Bool
== :: RestartFrameArguments -> RestartFrameArguments -> Bool
$c/= :: RestartFrameArguments -> RestartFrameArguments -> Bool
/= :: RestartFrameArguments -> RestartFrameArguments -> Bool
Eq, (forall x. RestartFrameArguments -> Rep RestartFrameArguments x)
-> (forall x. Rep RestartFrameArguments x -> RestartFrameArguments)
-> Generic RestartFrameArguments
forall x. Rep RestartFrameArguments x -> RestartFrameArguments
forall x. RestartFrameArguments -> Rep RestartFrameArguments x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. RestartFrameArguments -> Rep RestartFrameArguments x
from :: forall x. RestartFrameArguments -> Rep RestartFrameArguments x
$cto :: forall x. Rep RestartFrameArguments x -> RestartFrameArguments
to :: forall x. Rep RestartFrameArguments x -> RestartFrameArguments
Generic)
instance FromJSON RestartFrameArguments where
  parseJSON :: Value -> Parser RestartFrameArguments
parseJSON = Value -> Parser RestartFrameArguments
forall a.
(Generic a, GFromJSON Zero (Rep a), Typeable a) =>
Value -> Parser a
genericParseJSONWithModifier
data GotoArguments
  = GotoArguments
  { GotoArguments -> Int
gotoArgumentsThreadId :: Int
    
    
    
  , GotoArguments -> Int
gotoArgumentsTargetId :: Int
    
    
    
  } deriving stock (Int -> GotoArguments -> ShowS
[GotoArguments] -> ShowS
GotoArguments -> String
(Int -> GotoArguments -> ShowS)
-> (GotoArguments -> String)
-> ([GotoArguments] -> ShowS)
-> Show GotoArguments
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> GotoArguments -> ShowS
showsPrec :: Int -> GotoArguments -> ShowS
$cshow :: GotoArguments -> String
show :: GotoArguments -> String
$cshowList :: [GotoArguments] -> ShowS
showList :: [GotoArguments] -> ShowS
Show, GotoArguments -> GotoArguments -> Bool
(GotoArguments -> GotoArguments -> Bool)
-> (GotoArguments -> GotoArguments -> Bool) -> Eq GotoArguments
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: GotoArguments -> GotoArguments -> Bool
== :: GotoArguments -> GotoArguments -> Bool
$c/= :: GotoArguments -> GotoArguments -> Bool
/= :: GotoArguments -> GotoArguments -> Bool
Eq, (forall x. GotoArguments -> Rep GotoArguments x)
-> (forall x. Rep GotoArguments x -> GotoArguments)
-> Generic GotoArguments
forall x. Rep GotoArguments x -> GotoArguments
forall x. GotoArguments -> Rep GotoArguments x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. GotoArguments -> Rep GotoArguments x
from :: forall x. GotoArguments -> Rep GotoArguments x
$cto :: forall x. Rep GotoArguments x -> GotoArguments
to :: forall x. Rep GotoArguments x -> GotoArguments
Generic)
instance FromJSON GotoArguments where
  parseJSON :: Value -> Parser GotoArguments
parseJSON = Value -> Parser GotoArguments
forall a.
(Generic a, GFromJSON Zero (Rep a), Typeable a) =>
Value -> Parser a
genericParseJSONWithModifier
data PauseArguments
  = PauseArguments
  { PauseArguments -> Int
pauseArgumentsThreadId :: Int
    
    
    
  } deriving stock (Int -> PauseArguments -> ShowS
[PauseArguments] -> ShowS
PauseArguments -> String
(Int -> PauseArguments -> ShowS)
-> (PauseArguments -> String)
-> ([PauseArguments] -> ShowS)
-> Show PauseArguments
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> PauseArguments -> ShowS
showsPrec :: Int -> PauseArguments -> ShowS
$cshow :: PauseArguments -> String
show :: PauseArguments -> String
$cshowList :: [PauseArguments] -> ShowS
showList :: [PauseArguments] -> ShowS
Show, PauseArguments -> PauseArguments -> Bool
(PauseArguments -> PauseArguments -> Bool)
-> (PauseArguments -> PauseArguments -> Bool) -> Eq PauseArguments
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: PauseArguments -> PauseArguments -> Bool
== :: PauseArguments -> PauseArguments -> Bool
$c/= :: PauseArguments -> PauseArguments -> Bool
/= :: PauseArguments -> PauseArguments -> Bool
Eq, (forall x. PauseArguments -> Rep PauseArguments x)
-> (forall x. Rep PauseArguments x -> PauseArguments)
-> Generic PauseArguments
forall x. Rep PauseArguments x -> PauseArguments
forall x. PauseArguments -> Rep PauseArguments x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. PauseArguments -> Rep PauseArguments x
from :: forall x. PauseArguments -> Rep PauseArguments x
$cto :: forall x. Rep PauseArguments x -> PauseArguments
to :: forall x. Rep PauseArguments x -> PauseArguments
Generic)
instance FromJSON PauseArguments where
  parseJSON :: Value -> Parser PauseArguments
parseJSON = Value -> Parser PauseArguments
forall a.
(Generic a, GFromJSON Zero (Rep a), Typeable a) =>
Value -> Parser a
genericParseJSONWithModifier
data StackTraceArguments
  = StackTraceArguments
  { StackTraceArguments -> Int
stackTraceArgumentsThreadId :: Int
    
    
    
  , StackTraceArguments -> Maybe Int
stackTraceArgumentsStartFrame :: Maybe Int
    
    
    
  , StackTraceArguments -> Maybe Int
stackTraceArgumentsLevels :: Maybe Int
    
    
    
    
  , StackTraceArguments -> Maybe StackFrameFormat
stackTraceArgumentsFormat :: Maybe StackFrameFormat
    
    
    
    
    
  } deriving stock (Int -> StackTraceArguments -> ShowS
[StackTraceArguments] -> ShowS
StackTraceArguments -> String
(Int -> StackTraceArguments -> ShowS)
-> (StackTraceArguments -> String)
-> ([StackTraceArguments] -> ShowS)
-> Show StackTraceArguments
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> StackTraceArguments -> ShowS
showsPrec :: Int -> StackTraceArguments -> ShowS
$cshow :: StackTraceArguments -> String
show :: StackTraceArguments -> String
$cshowList :: [StackTraceArguments] -> ShowS
showList :: [StackTraceArguments] -> ShowS
Show, StackTraceArguments -> StackTraceArguments -> Bool
(StackTraceArguments -> StackTraceArguments -> Bool)
-> (StackTraceArguments -> StackTraceArguments -> Bool)
-> Eq StackTraceArguments
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: StackTraceArguments -> StackTraceArguments -> Bool
== :: StackTraceArguments -> StackTraceArguments -> Bool
$c/= :: StackTraceArguments -> StackTraceArguments -> Bool
/= :: StackTraceArguments -> StackTraceArguments -> Bool
Eq, (forall x. StackTraceArguments -> Rep StackTraceArguments x)
-> (forall x. Rep StackTraceArguments x -> StackTraceArguments)
-> Generic StackTraceArguments
forall x. Rep StackTraceArguments x -> StackTraceArguments
forall x. StackTraceArguments -> Rep StackTraceArguments x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. StackTraceArguments -> Rep StackTraceArguments x
from :: forall x. StackTraceArguments -> Rep StackTraceArguments x
$cto :: forall x. Rep StackTraceArguments x -> StackTraceArguments
to :: forall x. Rep StackTraceArguments x -> StackTraceArguments
Generic)
instance FromJSON StackTraceArguments where
  parseJSON :: Value -> Parser StackTraceArguments
parseJSON = Value -> Parser StackTraceArguments
forall a.
(Generic a, GFromJSON Zero (Rep a), Typeable a) =>
Value -> Parser a
genericParseJSONWithModifier
data StackFrameFormat
  = StackFrameFormat
  { StackFrameFormat -> Maybe Bool
stackFrameFormatParameters :: Maybe Bool
    
    
    
  , StackFrameFormat -> Maybe Bool
stackFrameFormatParameterTypes :: Maybe Bool
    
    
    
  , StackFrameFormat -> Maybe Bool
stackFrameFormatParameterNames :: Maybe Bool
    
    
    
  , StackFrameFormat -> Maybe Bool
stackFrameFormatParameterValues :: Maybe Bool
    
    
    
  , StackFrameFormat -> Maybe Bool
stackFrameFormatLine :: Maybe Bool
    
    
    
  , StackFrameFormat -> Maybe Bool
stackFrameFormatModule :: Maybe Bool
    
    
    
  , StackFrameFormat -> Maybe Bool
stackFrameFormatIncludeAll :: Maybe Bool
    
    
    
    
  , StackFrameFormat -> Maybe Bool
stackFrameFormatHex :: Maybe Bool
    
    
    
  } deriving stock (Int -> StackFrameFormat -> ShowS
[StackFrameFormat] -> ShowS
StackFrameFormat -> String
(Int -> StackFrameFormat -> ShowS)
-> (StackFrameFormat -> String)
-> ([StackFrameFormat] -> ShowS)
-> Show StackFrameFormat
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> StackFrameFormat -> ShowS
showsPrec :: Int -> StackFrameFormat -> ShowS
$cshow :: StackFrameFormat -> String
show :: StackFrameFormat -> String
$cshowList :: [StackFrameFormat] -> ShowS
showList :: [StackFrameFormat] -> ShowS
Show, StackFrameFormat -> StackFrameFormat -> Bool
(StackFrameFormat -> StackFrameFormat -> Bool)
-> (StackFrameFormat -> StackFrameFormat -> Bool)
-> Eq StackFrameFormat
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: StackFrameFormat -> StackFrameFormat -> Bool
== :: StackFrameFormat -> StackFrameFormat -> Bool
$c/= :: StackFrameFormat -> StackFrameFormat -> Bool
/= :: StackFrameFormat -> StackFrameFormat -> Bool
Eq, (forall x. StackFrameFormat -> Rep StackFrameFormat x)
-> (forall x. Rep StackFrameFormat x -> StackFrameFormat)
-> Generic StackFrameFormat
forall x. Rep StackFrameFormat x -> StackFrameFormat
forall x. StackFrameFormat -> Rep StackFrameFormat x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. StackFrameFormat -> Rep StackFrameFormat x
from :: forall x. StackFrameFormat -> Rep StackFrameFormat x
$cto :: forall x. Rep StackFrameFormat x -> StackFrameFormat
to :: forall x. Rep StackFrameFormat x -> StackFrameFormat
Generic)
defaultStackFrameFormat :: StackFrameFormat
defaultStackFrameFormat :: StackFrameFormat
defaultStackFrameFormat
  = StackFrameFormat
  { stackFrameFormatParameters :: Maybe Bool
stackFrameFormatParameters      = Maybe Bool
forall a. Maybe a
Nothing
  , stackFrameFormatParameterTypes :: Maybe Bool
stackFrameFormatParameterTypes  = Maybe Bool
forall a. Maybe a
Nothing
  , stackFrameFormatParameterNames :: Maybe Bool
stackFrameFormatParameterNames  = Maybe Bool
forall a. Maybe a
Nothing
  , stackFrameFormatParameterValues :: Maybe Bool
stackFrameFormatParameterValues = Maybe Bool
forall a. Maybe a
Nothing
  , stackFrameFormatLine :: Maybe Bool
stackFrameFormatLine            = Maybe Bool
forall a. Maybe a
Nothing
  , stackFrameFormatModule :: Maybe Bool
stackFrameFormatModule          = Maybe Bool
forall a. Maybe a
Nothing
  , stackFrameFormatIncludeAll :: Maybe Bool
stackFrameFormatIncludeAll      = Maybe Bool
forall a. Maybe a
Nothing
  , stackFrameFormatHex :: Maybe Bool
stackFrameFormatHex             = Maybe Bool
forall a. Maybe a
Nothing
  }
instance FromJSON StackFrameFormat where
  parseJSON :: Value -> Parser StackFrameFormat
parseJSON = Value -> Parser StackFrameFormat
forall a.
(Generic a, GFromJSON Zero (Rep a), Typeable a) =>
Value -> Parser a
genericParseJSONWithModifier
data ScopesArguments
  = ScopesArguments
  { ScopesArguments -> Int
scopesArgumentsFrameId :: Int
    
    
    
    
    
  } deriving stock (Int -> ScopesArguments -> ShowS
[ScopesArguments] -> ShowS
ScopesArguments -> String
(Int -> ScopesArguments -> ShowS)
-> (ScopesArguments -> String)
-> ([ScopesArguments] -> ShowS)
-> Show ScopesArguments
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ScopesArguments -> ShowS
showsPrec :: Int -> ScopesArguments -> ShowS
$cshow :: ScopesArguments -> String
show :: ScopesArguments -> String
$cshowList :: [ScopesArguments] -> ShowS
showList :: [ScopesArguments] -> ShowS
Show, ScopesArguments -> ScopesArguments -> Bool
(ScopesArguments -> ScopesArguments -> Bool)
-> (ScopesArguments -> ScopesArguments -> Bool)
-> Eq ScopesArguments
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ScopesArguments -> ScopesArguments -> Bool
== :: ScopesArguments -> ScopesArguments -> Bool
$c/= :: ScopesArguments -> ScopesArguments -> Bool
/= :: ScopesArguments -> ScopesArguments -> Bool
Eq, (forall x. ScopesArguments -> Rep ScopesArguments x)
-> (forall x. Rep ScopesArguments x -> ScopesArguments)
-> Generic ScopesArguments
forall x. Rep ScopesArguments x -> ScopesArguments
forall x. ScopesArguments -> Rep ScopesArguments x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ScopesArguments -> Rep ScopesArguments x
from :: forall x. ScopesArguments -> Rep ScopesArguments x
$cto :: forall x. Rep ScopesArguments x -> ScopesArguments
to :: forall x. Rep ScopesArguments x -> ScopesArguments
Generic)
instance FromJSON ScopesArguments where
  parseJSON :: Value -> Parser ScopesArguments
parseJSON = Value -> Parser ScopesArguments
forall a.
(Generic a, GFromJSON Zero (Rep a), Typeable a) =>
Value -> Parser a
genericParseJSONWithModifier
data VariablesFilter
  = VariablesFilterIndexed
  | VariablesFilterNamed
  deriving stock (Int -> VariablesFilter -> ShowS
[VariablesFilter] -> ShowS
VariablesFilter -> String
(Int -> VariablesFilter -> ShowS)
-> (VariablesFilter -> String)
-> ([VariablesFilter] -> ShowS)
-> Show VariablesFilter
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> VariablesFilter -> ShowS
showsPrec :: Int -> VariablesFilter -> ShowS
$cshow :: VariablesFilter -> String
show :: VariablesFilter -> String
$cshowList :: [VariablesFilter] -> ShowS
showList :: [VariablesFilter] -> ShowS
Show, VariablesFilter -> VariablesFilter -> Bool
(VariablesFilter -> VariablesFilter -> Bool)
-> (VariablesFilter -> VariablesFilter -> Bool)
-> Eq VariablesFilter
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: VariablesFilter -> VariablesFilter -> Bool
== :: VariablesFilter -> VariablesFilter -> Bool
$c/= :: VariablesFilter -> VariablesFilter -> Bool
/= :: VariablesFilter -> VariablesFilter -> Bool
Eq, (forall x. VariablesFilter -> Rep VariablesFilter x)
-> (forall x. Rep VariablesFilter x -> VariablesFilter)
-> Generic VariablesFilter
forall x. Rep VariablesFilter x -> VariablesFilter
forall x. VariablesFilter -> Rep VariablesFilter x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. VariablesFilter -> Rep VariablesFilter x
from :: forall x. VariablesFilter -> Rep VariablesFilter x
$cto :: forall x. Rep VariablesFilter x -> VariablesFilter
to :: forall x. Rep VariablesFilter x -> VariablesFilter
Generic)
instance FromJSON VariablesFilter where
  parseJSON :: Value -> Parser VariablesFilter
parseJSON = Value -> Parser VariablesFilter
forall a.
(Generic a, GFromJSON Zero (Rep a), Typeable a) =>
Value -> Parser a
genericParseJSONWithModifier
data VariablesArguments
  = VariablesArguments
  { VariablesArguments -> Int
variablesArgumentsVariablesReference :: Int
    
    
    
    
    
  , VariablesArguments -> Maybe VariablesFilter
variablesArgumentsFilter :: Maybe VariablesFilter
    
    
    
    
    
  , VariablesArguments -> Maybe Int
variablesArgumentsStart :: Maybe Int
    
    
    
  , VariablesArguments -> Maybe Int
variablesArgumentsCount :: Maybe Int
    
    
    
    
  , VariablesArguments -> Maybe ValueFormat
variablesArgumentsFormat :: Maybe ValueFormat
    
    
    
    
    
  } deriving stock (Int -> VariablesArguments -> ShowS
[VariablesArguments] -> ShowS
VariablesArguments -> String
(Int -> VariablesArguments -> ShowS)
-> (VariablesArguments -> String)
-> ([VariablesArguments] -> ShowS)
-> Show VariablesArguments
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> VariablesArguments -> ShowS
showsPrec :: Int -> VariablesArguments -> ShowS
$cshow :: VariablesArguments -> String
show :: VariablesArguments -> String
$cshowList :: [VariablesArguments] -> ShowS
showList :: [VariablesArguments] -> ShowS
Show, VariablesArguments -> VariablesArguments -> Bool
(VariablesArguments -> VariablesArguments -> Bool)
-> (VariablesArguments -> VariablesArguments -> Bool)
-> Eq VariablesArguments
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: VariablesArguments -> VariablesArguments -> Bool
== :: VariablesArguments -> VariablesArguments -> Bool
$c/= :: VariablesArguments -> VariablesArguments -> Bool
/= :: VariablesArguments -> VariablesArguments -> Bool
Eq, (forall x. VariablesArguments -> Rep VariablesArguments x)
-> (forall x. Rep VariablesArguments x -> VariablesArguments)
-> Generic VariablesArguments
forall x. Rep VariablesArguments x -> VariablesArguments
forall x. VariablesArguments -> Rep VariablesArguments x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. VariablesArguments -> Rep VariablesArguments x
from :: forall x. VariablesArguments -> Rep VariablesArguments x
$cto :: forall x. Rep VariablesArguments x -> VariablesArguments
to :: forall x. Rep VariablesArguments x -> VariablesArguments
Generic)
instance FromJSON VariablesArguments where
  parseJSON :: Value -> Parser VariablesArguments
parseJSON = Value -> Parser VariablesArguments
forall a.
(Generic a, GFromJSON Zero (Rep a), Typeable a) =>
Value -> Parser a
genericParseJSONWithModifier
data ValueFormat
  = ValueFormat
  { ValueFormat -> Maybe Bool
valueFormatHex :: Maybe Bool
    
    
    
  } deriving stock (Int -> ValueFormat -> ShowS
[ValueFormat] -> ShowS
ValueFormat -> String
(Int -> ValueFormat -> ShowS)
-> (ValueFormat -> String)
-> ([ValueFormat] -> ShowS)
-> Show ValueFormat
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ValueFormat -> ShowS
showsPrec :: Int -> ValueFormat -> ShowS
$cshow :: ValueFormat -> String
show :: ValueFormat -> String
$cshowList :: [ValueFormat] -> ShowS
showList :: [ValueFormat] -> ShowS
Show, ValueFormat -> ValueFormat -> Bool
(ValueFormat -> ValueFormat -> Bool)
-> (ValueFormat -> ValueFormat -> Bool) -> Eq ValueFormat
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ValueFormat -> ValueFormat -> Bool
== :: ValueFormat -> ValueFormat -> Bool
$c/= :: ValueFormat -> ValueFormat -> Bool
/= :: ValueFormat -> ValueFormat -> Bool
Eq, (forall x. ValueFormat -> Rep ValueFormat x)
-> (forall x. Rep ValueFormat x -> ValueFormat)
-> Generic ValueFormat
forall x. Rep ValueFormat x -> ValueFormat
forall x. ValueFormat -> Rep ValueFormat x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ValueFormat -> Rep ValueFormat x
from :: forall x. ValueFormat -> Rep ValueFormat x
$cto :: forall x. Rep ValueFormat x -> ValueFormat
to :: forall x. Rep ValueFormat x -> ValueFormat
Generic)
defaultValueFormat :: ValueFormat
defaultValueFormat :: ValueFormat
defaultValueFormat
  = ValueFormat
  { valueFormatHex :: Maybe Bool
valueFormatHex = Maybe Bool
forall a. Maybe a
Nothing
  }
instance FromJSON ValueFormat where
  parseJSON :: Value -> Parser ValueFormat
parseJSON = Value -> Parser ValueFormat
forall a.
(Generic a, GFromJSON Zero (Rep a), Typeable a) =>
Value -> Parser a
genericParseJSONWithModifier
data SetVariableArguments
  = SetVariableArguments
  { SetVariableArguments -> Int
setVariableArgumentsVariablesReference :: Int
    
    
    
    
    
  , SetVariableArguments -> Text
setVariableArgumentsName :: Text
    
    
    
  , SetVariableArguments -> Text
setVariableArgumentsValue :: Text
    
    
    
  , SetVariableArguments -> Maybe ValueFormat
setVariableArgumentsFormat :: Maybe ValueFormat
    
    
    
  } deriving stock (Int -> SetVariableArguments -> ShowS
[SetVariableArguments] -> ShowS
SetVariableArguments -> String
(Int -> SetVariableArguments -> ShowS)
-> (SetVariableArguments -> String)
-> ([SetVariableArguments] -> ShowS)
-> Show SetVariableArguments
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SetVariableArguments -> ShowS
showsPrec :: Int -> SetVariableArguments -> ShowS
$cshow :: SetVariableArguments -> String
show :: SetVariableArguments -> String
$cshowList :: [SetVariableArguments] -> ShowS
showList :: [SetVariableArguments] -> ShowS
Show, SetVariableArguments -> SetVariableArguments -> Bool
(SetVariableArguments -> SetVariableArguments -> Bool)
-> (SetVariableArguments -> SetVariableArguments -> Bool)
-> Eq SetVariableArguments
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SetVariableArguments -> SetVariableArguments -> Bool
== :: SetVariableArguments -> SetVariableArguments -> Bool
$c/= :: SetVariableArguments -> SetVariableArguments -> Bool
/= :: SetVariableArguments -> SetVariableArguments -> Bool
Eq, (forall x. SetVariableArguments -> Rep SetVariableArguments x)
-> (forall x. Rep SetVariableArguments x -> SetVariableArguments)
-> Generic SetVariableArguments
forall x. Rep SetVariableArguments x -> SetVariableArguments
forall x. SetVariableArguments -> Rep SetVariableArguments x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. SetVariableArguments -> Rep SetVariableArguments x
from :: forall x. SetVariableArguments -> Rep SetVariableArguments x
$cto :: forall x. Rep SetVariableArguments x -> SetVariableArguments
to :: forall x. Rep SetVariableArguments x -> SetVariableArguments
Generic)
instance FromJSON SetVariableArguments where
  parseJSON :: Value -> Parser SetVariableArguments
parseJSON = Value -> Parser SetVariableArguments
forall a.
(Generic a, GFromJSON Zero (Rep a), Typeable a) =>
Value -> Parser a
genericParseJSONWithModifier
data SourceArguments
  = SourceArguments
  { SourceArguments -> Maybe Source
sourceArgumentsSource :: Maybe Source
    
    
    
    
  , SourceArguments -> Int
sourceArgumentsSourceReference :: Int
    
    
    
    
    
  } deriving stock (Int -> SourceArguments -> ShowS
[SourceArguments] -> ShowS
SourceArguments -> String
(Int -> SourceArguments -> ShowS)
-> (SourceArguments -> String)
-> ([SourceArguments] -> ShowS)
-> Show SourceArguments
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SourceArguments -> ShowS
showsPrec :: Int -> SourceArguments -> ShowS
$cshow :: SourceArguments -> String
show :: SourceArguments -> String
$cshowList :: [SourceArguments] -> ShowS
showList :: [SourceArguments] -> ShowS
Show, SourceArguments -> SourceArguments -> Bool
(SourceArguments -> SourceArguments -> Bool)
-> (SourceArguments -> SourceArguments -> Bool)
-> Eq SourceArguments
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SourceArguments -> SourceArguments -> Bool
== :: SourceArguments -> SourceArguments -> Bool
$c/= :: SourceArguments -> SourceArguments -> Bool
/= :: SourceArguments -> SourceArguments -> Bool
Eq, (forall x. SourceArguments -> Rep SourceArguments x)
-> (forall x. Rep SourceArguments x -> SourceArguments)
-> Generic SourceArguments
forall x. Rep SourceArguments x -> SourceArguments
forall x. SourceArguments -> Rep SourceArguments x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. SourceArguments -> Rep SourceArguments x
from :: forall x. SourceArguments -> Rep SourceArguments x
$cto :: forall x. Rep SourceArguments x -> SourceArguments
to :: forall x. Rep SourceArguments x -> SourceArguments
Generic)
instance FromJSON SourceArguments where
  parseJSON :: Value -> Parser SourceArguments
parseJSON = Value -> Parser SourceArguments
forall a.
(Generic a, GFromJSON Zero (Rep a), Typeable a) =>
Value -> Parser a
genericParseJSONWithModifier
newtype TerminateThreadsArguments
  = TerminateThreadsArguments
  { TerminateThreadsArguments -> [Int]
terminateThreadsArgumentsThreadIds :: [Int]
    
    
    
  } deriving stock (Int -> TerminateThreadsArguments -> ShowS
[TerminateThreadsArguments] -> ShowS
TerminateThreadsArguments -> String
(Int -> TerminateThreadsArguments -> ShowS)
-> (TerminateThreadsArguments -> String)
-> ([TerminateThreadsArguments] -> ShowS)
-> Show TerminateThreadsArguments
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TerminateThreadsArguments -> ShowS
showsPrec :: Int -> TerminateThreadsArguments -> ShowS
$cshow :: TerminateThreadsArguments -> String
show :: TerminateThreadsArguments -> String
$cshowList :: [TerminateThreadsArguments] -> ShowS
showList :: [TerminateThreadsArguments] -> ShowS
Show, TerminateThreadsArguments -> TerminateThreadsArguments -> Bool
(TerminateThreadsArguments -> TerminateThreadsArguments -> Bool)
-> (TerminateThreadsArguments -> TerminateThreadsArguments -> Bool)
-> Eq TerminateThreadsArguments
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TerminateThreadsArguments -> TerminateThreadsArguments -> Bool
== :: TerminateThreadsArguments -> TerminateThreadsArguments -> Bool
$c/= :: TerminateThreadsArguments -> TerminateThreadsArguments -> Bool
/= :: TerminateThreadsArguments -> TerminateThreadsArguments -> Bool
Eq, (forall x.
 TerminateThreadsArguments -> Rep TerminateThreadsArguments x)
-> (forall x.
    Rep TerminateThreadsArguments x -> TerminateThreadsArguments)
-> Generic TerminateThreadsArguments
forall x.
Rep TerminateThreadsArguments x -> TerminateThreadsArguments
forall x.
TerminateThreadsArguments -> Rep TerminateThreadsArguments x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x.
TerminateThreadsArguments -> Rep TerminateThreadsArguments x
from :: forall x.
TerminateThreadsArguments -> Rep TerminateThreadsArguments x
$cto :: forall x.
Rep TerminateThreadsArguments x -> TerminateThreadsArguments
to :: forall x.
Rep TerminateThreadsArguments x -> TerminateThreadsArguments
Generic)
instance FromJSON TerminateThreadsArguments where
  parseJSON :: Value -> Parser TerminateThreadsArguments
parseJSON = Value -> Parser TerminateThreadsArguments
forall a.
(Generic a, GFromJSON Zero (Rep a), Typeable a) =>
Value -> Parser a
genericParseJSONWithModifier
data ModulesArguments
  = ModulesArguments
  { ModulesArguments -> Maybe Int
modulesArgumentsStartModule :: Maybe Int
    
    
    
  , ModulesArguments -> Maybe Int
modulesArgumentsModuleCount :: Maybe Int
    
    
    
    
  } deriving stock (Int -> ModulesArguments -> ShowS
[ModulesArguments] -> ShowS
ModulesArguments -> String
(Int -> ModulesArguments -> ShowS)
-> (ModulesArguments -> String)
-> ([ModulesArguments] -> ShowS)
-> Show ModulesArguments
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ModulesArguments -> ShowS
showsPrec :: Int -> ModulesArguments -> ShowS
$cshow :: ModulesArguments -> String
show :: ModulesArguments -> String
$cshowList :: [ModulesArguments] -> ShowS
showList :: [ModulesArguments] -> ShowS
Show, ModulesArguments -> ModulesArguments -> Bool
(ModulesArguments -> ModulesArguments -> Bool)
-> (ModulesArguments -> ModulesArguments -> Bool)
-> Eq ModulesArguments
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ModulesArguments -> ModulesArguments -> Bool
== :: ModulesArguments -> ModulesArguments -> Bool
$c/= :: ModulesArguments -> ModulesArguments -> Bool
/= :: ModulesArguments -> ModulesArguments -> Bool
Eq, (forall x. ModulesArguments -> Rep ModulesArguments x)
-> (forall x. Rep ModulesArguments x -> ModulesArguments)
-> Generic ModulesArguments
forall x. Rep ModulesArguments x -> ModulesArguments
forall x. ModulesArguments -> Rep ModulesArguments x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ModulesArguments -> Rep ModulesArguments x
from :: forall x. ModulesArguments -> Rep ModulesArguments x
$cto :: forall x. Rep ModulesArguments x -> ModulesArguments
to :: forall x. Rep ModulesArguments x -> ModulesArguments
Generic)
data LoadedSourcesArguments = LoadedSourcesArguments
  deriving stock (Int -> LoadedSourcesArguments -> ShowS
[LoadedSourcesArguments] -> ShowS
LoadedSourcesArguments -> String
(Int -> LoadedSourcesArguments -> ShowS)
-> (LoadedSourcesArguments -> String)
-> ([LoadedSourcesArguments] -> ShowS)
-> Show LoadedSourcesArguments
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> LoadedSourcesArguments -> ShowS
showsPrec :: Int -> LoadedSourcesArguments -> ShowS
$cshow :: LoadedSourcesArguments -> String
show :: LoadedSourcesArguments -> String
$cshowList :: [LoadedSourcesArguments] -> ShowS
showList :: [LoadedSourcesArguments] -> ShowS
Show, LoadedSourcesArguments -> LoadedSourcesArguments -> Bool
(LoadedSourcesArguments -> LoadedSourcesArguments -> Bool)
-> (LoadedSourcesArguments -> LoadedSourcesArguments -> Bool)
-> Eq LoadedSourcesArguments
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: LoadedSourcesArguments -> LoadedSourcesArguments -> Bool
== :: LoadedSourcesArguments -> LoadedSourcesArguments -> Bool
$c/= :: LoadedSourcesArguments -> LoadedSourcesArguments -> Bool
/= :: LoadedSourcesArguments -> LoadedSourcesArguments -> Bool
Eq)
instance FromJSON LoadedSourcesArguments where
  parseJSON :: Value -> Parser LoadedSourcesArguments
parseJSON Value
_ = LoadedSourcesArguments -> Parser LoadedSourcesArguments
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure LoadedSourcesArguments
LoadedSourcesArguments
data EvaluateArgumentsContext
  = EvaluateArgumentsContextWatch
  | EvaluateArgumentsContextRepl
  | EvaluateArgumentsContextHover
  | EvaluateArgumentsContextClipboard
  | EvaluateArgumentsContextVariable
  deriving stock (Int -> EvaluateArgumentsContext -> ShowS
[EvaluateArgumentsContext] -> ShowS
EvaluateArgumentsContext -> String
(Int -> EvaluateArgumentsContext -> ShowS)
-> (EvaluateArgumentsContext -> String)
-> ([EvaluateArgumentsContext] -> ShowS)
-> Show EvaluateArgumentsContext
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> EvaluateArgumentsContext -> ShowS
showsPrec :: Int -> EvaluateArgumentsContext -> ShowS
$cshow :: EvaluateArgumentsContext -> String
show :: EvaluateArgumentsContext -> String
$cshowList :: [EvaluateArgumentsContext] -> ShowS
showList :: [EvaluateArgumentsContext] -> ShowS
Show, EvaluateArgumentsContext -> EvaluateArgumentsContext -> Bool
(EvaluateArgumentsContext -> EvaluateArgumentsContext -> Bool)
-> (EvaluateArgumentsContext -> EvaluateArgumentsContext -> Bool)
-> Eq EvaluateArgumentsContext
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: EvaluateArgumentsContext -> EvaluateArgumentsContext -> Bool
== :: EvaluateArgumentsContext -> EvaluateArgumentsContext -> Bool
$c/= :: EvaluateArgumentsContext -> EvaluateArgumentsContext -> Bool
/= :: EvaluateArgumentsContext -> EvaluateArgumentsContext -> Bool
Eq, (forall x.
 EvaluateArgumentsContext -> Rep EvaluateArgumentsContext x)
-> (forall x.
    Rep EvaluateArgumentsContext x -> EvaluateArgumentsContext)
-> Generic EvaluateArgumentsContext
forall x.
Rep EvaluateArgumentsContext x -> EvaluateArgumentsContext
forall x.
EvaluateArgumentsContext -> Rep EvaluateArgumentsContext x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x.
EvaluateArgumentsContext -> Rep EvaluateArgumentsContext x
from :: forall x.
EvaluateArgumentsContext -> Rep EvaluateArgumentsContext x
$cto :: forall x.
Rep EvaluateArgumentsContext x -> EvaluateArgumentsContext
to :: forall x.
Rep EvaluateArgumentsContext x -> EvaluateArgumentsContext
Generic)
instance ToJSON EvaluateArgumentsContext where
  toJSON :: EvaluateArgumentsContext -> Value
toJSON = EvaluateArgumentsContext -> Value
forall a.
(Generic a, GToJSON Zero (Rep a), Typeable a) =>
a -> Value
genericToJSONWithModifier
instance FromJSON EvaluateArgumentsContext where
  parseJSON :: Value -> Parser EvaluateArgumentsContext
parseJSON = Value -> Parser EvaluateArgumentsContext
forall a.
(Generic a, GFromJSON Zero (Rep a), Typeable a) =>
Value -> Parser a
genericParseJSONWithModifier
data EvaluateArguments
  = EvaluateArguments
  { EvaluateArguments -> Text
evaluateArgumentsExpression :: Text
    
    
    
  , EvaluateArguments -> Maybe Int
evaluateArgumentsFrameId:: Maybe Int
    
    
    
    
  , EvaluateArguments -> Maybe EvaluateArgumentsContext
evaluateArgumentsContext :: Maybe EvaluateArgumentsContext
    
    
    
    
    
    
    
    
    
    
    
    
    
    
  , EvaluateArguments -> Maybe ValueFormat
evaluateArgumentsFormat :: Maybe ValueFormat
    
    
    
    
    
  } deriving stock (Int -> EvaluateArguments -> ShowS
[EvaluateArguments] -> ShowS
EvaluateArguments -> String
(Int -> EvaluateArguments -> ShowS)
-> (EvaluateArguments -> String)
-> ([EvaluateArguments] -> ShowS)
-> Show EvaluateArguments
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> EvaluateArguments -> ShowS
showsPrec :: Int -> EvaluateArguments -> ShowS
$cshow :: EvaluateArguments -> String
show :: EvaluateArguments -> String
$cshowList :: [EvaluateArguments] -> ShowS
showList :: [EvaluateArguments] -> ShowS
Show, EvaluateArguments -> EvaluateArguments -> Bool
(EvaluateArguments -> EvaluateArguments -> Bool)
-> (EvaluateArguments -> EvaluateArguments -> Bool)
-> Eq EvaluateArguments
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: EvaluateArguments -> EvaluateArguments -> Bool
== :: EvaluateArguments -> EvaluateArguments -> Bool
$c/= :: EvaluateArguments -> EvaluateArguments -> Bool
/= :: EvaluateArguments -> EvaluateArguments -> Bool
Eq, (forall x. EvaluateArguments -> Rep EvaluateArguments x)
-> (forall x. Rep EvaluateArguments x -> EvaluateArguments)
-> Generic EvaluateArguments
forall x. Rep EvaluateArguments x -> EvaluateArguments
forall x. EvaluateArguments -> Rep EvaluateArguments x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. EvaluateArguments -> Rep EvaluateArguments x
from :: forall x. EvaluateArguments -> Rep EvaluateArguments x
$cto :: forall x. Rep EvaluateArguments x -> EvaluateArguments
to :: forall x. Rep EvaluateArguments x -> EvaluateArguments
Generic)
instance FromJSON EvaluateArguments where
  parseJSON :: Value -> Parser EvaluateArguments
parseJSON = Value -> Parser EvaluateArguments
forall a.
(Generic a, GFromJSON Zero (Rep a), Typeable a) =>
Value -> Parser a
genericParseJSONWithModifier
data SetExpressionArguments
  = SetExpressionArguments
  { SetExpressionArguments -> Text
setExpressionArgumentsExpression :: Text
    
    
    
  , SetExpressionArguments -> Text
setExpressionArgumentsValue :: Text
    
    
    
  , SetExpressionArguments -> Maybe Int
setExpressionArgumentsFrameId :: Maybe Int
    
    
    
    
  , SetExpressionArguments -> Maybe ValueFormat
setExpressionArgumentsFormat :: Maybe ValueFormat
    
    
    
  } deriving stock (Int -> SetExpressionArguments -> ShowS
[SetExpressionArguments] -> ShowS
SetExpressionArguments -> String
(Int -> SetExpressionArguments -> ShowS)
-> (SetExpressionArguments -> String)
-> ([SetExpressionArguments] -> ShowS)
-> Show SetExpressionArguments
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SetExpressionArguments -> ShowS
showsPrec :: Int -> SetExpressionArguments -> ShowS
$cshow :: SetExpressionArguments -> String
show :: SetExpressionArguments -> String
$cshowList :: [SetExpressionArguments] -> ShowS
showList :: [SetExpressionArguments] -> ShowS
Show, SetExpressionArguments -> SetExpressionArguments -> Bool
(SetExpressionArguments -> SetExpressionArguments -> Bool)
-> (SetExpressionArguments -> SetExpressionArguments -> Bool)
-> Eq SetExpressionArguments
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SetExpressionArguments -> SetExpressionArguments -> Bool
== :: SetExpressionArguments -> SetExpressionArguments -> Bool
$c/= :: SetExpressionArguments -> SetExpressionArguments -> Bool
/= :: SetExpressionArguments -> SetExpressionArguments -> Bool
Eq, (forall x. SetExpressionArguments -> Rep SetExpressionArguments x)
-> (forall x.
    Rep SetExpressionArguments x -> SetExpressionArguments)
-> Generic SetExpressionArguments
forall x. Rep SetExpressionArguments x -> SetExpressionArguments
forall x. SetExpressionArguments -> Rep SetExpressionArguments x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. SetExpressionArguments -> Rep SetExpressionArguments x
from :: forall x. SetExpressionArguments -> Rep SetExpressionArguments x
$cto :: forall x. Rep SetExpressionArguments x -> SetExpressionArguments
to :: forall x. Rep SetExpressionArguments x -> SetExpressionArguments
Generic)
instance FromJSON SetExpressionArguments where
  parseJSON :: Value -> Parser SetExpressionArguments
parseJSON = Value -> Parser SetExpressionArguments
forall a.
(Generic a, GFromJSON Zero (Rep a), Typeable a) =>
Value -> Parser a
genericParseJSONWithModifier
data StepInTargetsArguments
  = StepInTargetsArguments
  { StepInTargetsArguments -> Int
stepInTargetsArgumentsFrameId :: Int
    
    
    
  } deriving stock (Int -> StepInTargetsArguments -> ShowS
[StepInTargetsArguments] -> ShowS
StepInTargetsArguments -> String
(Int -> StepInTargetsArguments -> ShowS)
-> (StepInTargetsArguments -> String)
-> ([StepInTargetsArguments] -> ShowS)
-> Show StepInTargetsArguments
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> StepInTargetsArguments -> ShowS
showsPrec :: Int -> StepInTargetsArguments -> ShowS
$cshow :: StepInTargetsArguments -> String
show :: StepInTargetsArguments -> String
$cshowList :: [StepInTargetsArguments] -> ShowS
showList :: [StepInTargetsArguments] -> ShowS
Show, StepInTargetsArguments -> StepInTargetsArguments -> Bool
(StepInTargetsArguments -> StepInTargetsArguments -> Bool)
-> (StepInTargetsArguments -> StepInTargetsArguments -> Bool)
-> Eq StepInTargetsArguments
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: StepInTargetsArguments -> StepInTargetsArguments -> Bool
== :: StepInTargetsArguments -> StepInTargetsArguments -> Bool
$c/= :: StepInTargetsArguments -> StepInTargetsArguments -> Bool
/= :: StepInTargetsArguments -> StepInTargetsArguments -> Bool
Eq, (forall x. StepInTargetsArguments -> Rep StepInTargetsArguments x)
-> (forall x.
    Rep StepInTargetsArguments x -> StepInTargetsArguments)
-> Generic StepInTargetsArguments
forall x. Rep StepInTargetsArguments x -> StepInTargetsArguments
forall x. StepInTargetsArguments -> Rep StepInTargetsArguments x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. StepInTargetsArguments -> Rep StepInTargetsArguments x
from :: forall x. StepInTargetsArguments -> Rep StepInTargetsArguments x
$cto :: forall x. Rep StepInTargetsArguments x -> StepInTargetsArguments
to :: forall x. Rep StepInTargetsArguments x -> StepInTargetsArguments
Generic)
instance FromJSON StepInTargetsArguments where
  parseJSON :: Value -> Parser StepInTargetsArguments
parseJSON = Value -> Parser StepInTargetsArguments
forall a.
(Generic a, GFromJSON Zero (Rep a), Typeable a) =>
Value -> Parser a
genericParseJSONWithModifier
data GotoTargetsArguments
  = GotoTargetsArguments
  { GotoTargetsArguments -> Source
gotoTargetsArgumentsSource :: Source
    
    
    
  , GotoTargetsArguments -> Int
gotoTargetsArgumentsLine :: Int
    
    
    
  , GotoTargetsArguments -> Maybe Int
gotoTargetsArgumentsColumn :: Maybe Int
    
    
    
    
    
  } deriving stock (Int -> GotoTargetsArguments -> ShowS
[GotoTargetsArguments] -> ShowS
GotoTargetsArguments -> String
(Int -> GotoTargetsArguments -> ShowS)
-> (GotoTargetsArguments -> String)
-> ([GotoTargetsArguments] -> ShowS)
-> Show GotoTargetsArguments
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> GotoTargetsArguments -> ShowS
showsPrec :: Int -> GotoTargetsArguments -> ShowS
$cshow :: GotoTargetsArguments -> String
show :: GotoTargetsArguments -> String
$cshowList :: [GotoTargetsArguments] -> ShowS
showList :: [GotoTargetsArguments] -> ShowS
Show, GotoTargetsArguments -> GotoTargetsArguments -> Bool
(GotoTargetsArguments -> GotoTargetsArguments -> Bool)
-> (GotoTargetsArguments -> GotoTargetsArguments -> Bool)
-> Eq GotoTargetsArguments
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: GotoTargetsArguments -> GotoTargetsArguments -> Bool
== :: GotoTargetsArguments -> GotoTargetsArguments -> Bool
$c/= :: GotoTargetsArguments -> GotoTargetsArguments -> Bool
/= :: GotoTargetsArguments -> GotoTargetsArguments -> Bool
Eq, (forall x. GotoTargetsArguments -> Rep GotoTargetsArguments x)
-> (forall x. Rep GotoTargetsArguments x -> GotoTargetsArguments)
-> Generic GotoTargetsArguments
forall x. Rep GotoTargetsArguments x -> GotoTargetsArguments
forall x. GotoTargetsArguments -> Rep GotoTargetsArguments x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. GotoTargetsArguments -> Rep GotoTargetsArguments x
from :: forall x. GotoTargetsArguments -> Rep GotoTargetsArguments x
$cto :: forall x. Rep GotoTargetsArguments x -> GotoTargetsArguments
to :: forall x. Rep GotoTargetsArguments x -> GotoTargetsArguments
Generic)
instance FromJSON GotoTargetsArguments where
  parseJSON :: Value -> Parser GotoTargetsArguments
parseJSON = Value -> Parser GotoTargetsArguments
forall a.
(Generic a, GFromJSON Zero (Rep a), Typeable a) =>
Value -> Parser a
genericParseJSONWithModifier
data CompletionsArguments
  = CompletionsArguments
  { CompletionsArguments -> Maybe Int
completionsArgumentsFrameId :: Maybe Int
    
    
    
    
  , CompletionsArguments -> Text
completionsArgumentsText :: Text
    
    
    
    
  , CompletionsArguments -> Int
completionsArgumentsColumn :: Int
    
    
    
    
    
  , CompletionsArguments -> Maybe Int
completionsArgumentsLine :: Maybe Int
    
    
    
    
  } deriving stock (Int -> CompletionsArguments -> ShowS
[CompletionsArguments] -> ShowS
CompletionsArguments -> String
(Int -> CompletionsArguments -> ShowS)
-> (CompletionsArguments -> String)
-> ([CompletionsArguments] -> ShowS)
-> Show CompletionsArguments
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CompletionsArguments -> ShowS
showsPrec :: Int -> CompletionsArguments -> ShowS
$cshow :: CompletionsArguments -> String
show :: CompletionsArguments -> String
$cshowList :: [CompletionsArguments] -> ShowS
showList :: [CompletionsArguments] -> ShowS
Show, CompletionsArguments -> CompletionsArguments -> Bool
(CompletionsArguments -> CompletionsArguments -> Bool)
-> (CompletionsArguments -> CompletionsArguments -> Bool)
-> Eq CompletionsArguments
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CompletionsArguments -> CompletionsArguments -> Bool
== :: CompletionsArguments -> CompletionsArguments -> Bool
$c/= :: CompletionsArguments -> CompletionsArguments -> Bool
/= :: CompletionsArguments -> CompletionsArguments -> Bool
Eq, (forall x. CompletionsArguments -> Rep CompletionsArguments x)
-> (forall x. Rep CompletionsArguments x -> CompletionsArguments)
-> Generic CompletionsArguments
forall x. Rep CompletionsArguments x -> CompletionsArguments
forall x. CompletionsArguments -> Rep CompletionsArguments x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. CompletionsArguments -> Rep CompletionsArguments x
from :: forall x. CompletionsArguments -> Rep CompletionsArguments x
$cto :: forall x. Rep CompletionsArguments x -> CompletionsArguments
to :: forall x. Rep CompletionsArguments x -> CompletionsArguments
Generic)
instance FromJSON CompletionsArguments where
  parseJSON :: Value -> Parser CompletionsArguments
parseJSON = Value -> Parser CompletionsArguments
forall a.
(Generic a, GFromJSON Zero (Rep a), Typeable a) =>
Value -> Parser a
genericParseJSONWithModifier
data ExceptionInfoArguments
  = ExceptionInfoArguments
  { ExceptionInfoArguments -> Int
exceptionInfoArgumentsThreadId :: Int
    
    
    
  } deriving stock (Int -> ExceptionInfoArguments -> ShowS
[ExceptionInfoArguments] -> ShowS
ExceptionInfoArguments -> String
(Int -> ExceptionInfoArguments -> ShowS)
-> (ExceptionInfoArguments -> String)
-> ([ExceptionInfoArguments] -> ShowS)
-> Show ExceptionInfoArguments
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ExceptionInfoArguments -> ShowS
showsPrec :: Int -> ExceptionInfoArguments -> ShowS
$cshow :: ExceptionInfoArguments -> String
show :: ExceptionInfoArguments -> String
$cshowList :: [ExceptionInfoArguments] -> ShowS
showList :: [ExceptionInfoArguments] -> ShowS
Show, ExceptionInfoArguments -> ExceptionInfoArguments -> Bool
(ExceptionInfoArguments -> ExceptionInfoArguments -> Bool)
-> (ExceptionInfoArguments -> ExceptionInfoArguments -> Bool)
-> Eq ExceptionInfoArguments
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ExceptionInfoArguments -> ExceptionInfoArguments -> Bool
== :: ExceptionInfoArguments -> ExceptionInfoArguments -> Bool
$c/= :: ExceptionInfoArguments -> ExceptionInfoArguments -> Bool
/= :: ExceptionInfoArguments -> ExceptionInfoArguments -> Bool
Eq, (forall x. ExceptionInfoArguments -> Rep ExceptionInfoArguments x)
-> (forall x.
    Rep ExceptionInfoArguments x -> ExceptionInfoArguments)
-> Generic ExceptionInfoArguments
forall x. Rep ExceptionInfoArguments x -> ExceptionInfoArguments
forall x. ExceptionInfoArguments -> Rep ExceptionInfoArguments x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ExceptionInfoArguments -> Rep ExceptionInfoArguments x
from :: forall x. ExceptionInfoArguments -> Rep ExceptionInfoArguments x
$cto :: forall x. Rep ExceptionInfoArguments x -> ExceptionInfoArguments
to :: forall x. Rep ExceptionInfoArguments x -> ExceptionInfoArguments
Generic)
instance FromJSON ExceptionInfoArguments where
  parseJSON :: Value -> Parser ExceptionInfoArguments
parseJSON = Value -> Parser ExceptionInfoArguments
forall a.
(Generic a, GFromJSON Zero (Rep a), Typeable a) =>
Value -> Parser a
genericParseJSONWithModifier
data ReadMemoryArguments
  = ReadMemoryArguments
  { ReadMemoryArguments -> Text
readMemoryArgumentsmemoryReference :: Text
    
    
    
  , ReadMemoryArguments -> Maybe Int
readMemoryArgumentsOffset :: Maybe Int
    
    
    
    
  , ReadMemoryArguments -> Int
readMemoryArgumentsCount :: Int
    
    
    
  } deriving stock (Int -> ReadMemoryArguments -> ShowS
[ReadMemoryArguments] -> ShowS
ReadMemoryArguments -> String
(Int -> ReadMemoryArguments -> ShowS)
-> (ReadMemoryArguments -> String)
-> ([ReadMemoryArguments] -> ShowS)
-> Show ReadMemoryArguments
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ReadMemoryArguments -> ShowS
showsPrec :: Int -> ReadMemoryArguments -> ShowS
$cshow :: ReadMemoryArguments -> String
show :: ReadMemoryArguments -> String
$cshowList :: [ReadMemoryArguments] -> ShowS
showList :: [ReadMemoryArguments] -> ShowS
Show, ReadMemoryArguments -> ReadMemoryArguments -> Bool
(ReadMemoryArguments -> ReadMemoryArguments -> Bool)
-> (ReadMemoryArguments -> ReadMemoryArguments -> Bool)
-> Eq ReadMemoryArguments
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ReadMemoryArguments -> ReadMemoryArguments -> Bool
== :: ReadMemoryArguments -> ReadMemoryArguments -> Bool
$c/= :: ReadMemoryArguments -> ReadMemoryArguments -> Bool
/= :: ReadMemoryArguments -> ReadMemoryArguments -> Bool
Eq, (forall x. ReadMemoryArguments -> Rep ReadMemoryArguments x)
-> (forall x. Rep ReadMemoryArguments x -> ReadMemoryArguments)
-> Generic ReadMemoryArguments
forall x. Rep ReadMemoryArguments x -> ReadMemoryArguments
forall x. ReadMemoryArguments -> Rep ReadMemoryArguments x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ReadMemoryArguments -> Rep ReadMemoryArguments x
from :: forall x. ReadMemoryArguments -> Rep ReadMemoryArguments x
$cto :: forall x. Rep ReadMemoryArguments x -> ReadMemoryArguments
to :: forall x. Rep ReadMemoryArguments x -> ReadMemoryArguments
Generic)
instance FromJSON ReadMemoryArguments where
  parseJSON :: Value -> Parser ReadMemoryArguments
parseJSON = Value -> Parser ReadMemoryArguments
forall a.
(Generic a, GFromJSON Zero (Rep a), Typeable a) =>
Value -> Parser a
genericParseJSONWithModifier
data WriteMemoryArguments
  = WriteMemoryArguments
  { WriteMemoryArguments -> Text
writeMemoryMemoryReference :: Text
    
    
    
  , WriteMemoryArguments -> Maybe Int
writeMemoryArgumentsOffset :: Maybe Int
    
    
    
    
  , WriteMemoryArguments -> Bool
writeMemoryArgumentsAllowPartial :: Bool
    
    
    
    
    
    
    
    
    
  , WriteMemoryArguments -> Text
writeMemoryArgumentsData :: Text
    
    
    
  } deriving stock (Int -> WriteMemoryArguments -> ShowS
[WriteMemoryArguments] -> ShowS
WriteMemoryArguments -> String
(Int -> WriteMemoryArguments -> ShowS)
-> (WriteMemoryArguments -> String)
-> ([WriteMemoryArguments] -> ShowS)
-> Show WriteMemoryArguments
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> WriteMemoryArguments -> ShowS
showsPrec :: Int -> WriteMemoryArguments -> ShowS
$cshow :: WriteMemoryArguments -> String
show :: WriteMemoryArguments -> String
$cshowList :: [WriteMemoryArguments] -> ShowS
showList :: [WriteMemoryArguments] -> ShowS
Show, WriteMemoryArguments -> WriteMemoryArguments -> Bool
(WriteMemoryArguments -> WriteMemoryArguments -> Bool)
-> (WriteMemoryArguments -> WriteMemoryArguments -> Bool)
-> Eq WriteMemoryArguments
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: WriteMemoryArguments -> WriteMemoryArguments -> Bool
== :: WriteMemoryArguments -> WriteMemoryArguments -> Bool
$c/= :: WriteMemoryArguments -> WriteMemoryArguments -> Bool
/= :: WriteMemoryArguments -> WriteMemoryArguments -> Bool
Eq, (forall x. WriteMemoryArguments -> Rep WriteMemoryArguments x)
-> (forall x. Rep WriteMemoryArguments x -> WriteMemoryArguments)
-> Generic WriteMemoryArguments
forall x. Rep WriteMemoryArguments x -> WriteMemoryArguments
forall x. WriteMemoryArguments -> Rep WriteMemoryArguments x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. WriteMemoryArguments -> Rep WriteMemoryArguments x
from :: forall x. WriteMemoryArguments -> Rep WriteMemoryArguments x
$cto :: forall x. Rep WriteMemoryArguments x -> WriteMemoryArguments
to :: forall x. Rep WriteMemoryArguments x -> WriteMemoryArguments
Generic)
instance FromJSON WriteMemoryArguments where
  parseJSON :: Value -> Parser WriteMemoryArguments
parseJSON = Value -> Parser WriteMemoryArguments
forall a.
(Generic a, GFromJSON Zero (Rep a), Typeable a) =>
Value -> Parser a
genericParseJSONWithModifier
data DisassembleArguments
  = DisassembleArguments
  { DisassembleArguments -> Text
disassembleArgumentsMemoryReference :: Text
    
    
    
    
  , DisassembleArguments -> Maybe Int
disassembleArgumentsOffset :: Maybe Int
    
    
    
    
  , DisassembleArguments -> Maybe Int
disassembleArgumentsInstructionOffset :: Maybe Int
    
    
    
    
  , DisassembleArguments -> Int
disassembleArgumentsInstructionCount :: Int
    
    
    
    
    
    
    
  , DisassembleArguments -> Bool
disassembleArgumentsResolveSymbols :: Bool
    
    
    
    
   } deriving stock (Int -> DisassembleArguments -> ShowS
[DisassembleArguments] -> ShowS
DisassembleArguments -> String
(Int -> DisassembleArguments -> ShowS)
-> (DisassembleArguments -> String)
-> ([DisassembleArguments] -> ShowS)
-> Show DisassembleArguments
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> DisassembleArguments -> ShowS
showsPrec :: Int -> DisassembleArguments -> ShowS
$cshow :: DisassembleArguments -> String
show :: DisassembleArguments -> String
$cshowList :: [DisassembleArguments] -> ShowS
showList :: [DisassembleArguments] -> ShowS
Show, DisassembleArguments -> DisassembleArguments -> Bool
(DisassembleArguments -> DisassembleArguments -> Bool)
-> (DisassembleArguments -> DisassembleArguments -> Bool)
-> Eq DisassembleArguments
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DisassembleArguments -> DisassembleArguments -> Bool
== :: DisassembleArguments -> DisassembleArguments -> Bool
$c/= :: DisassembleArguments -> DisassembleArguments -> Bool
/= :: DisassembleArguments -> DisassembleArguments -> Bool
Eq, (forall x. DisassembleArguments -> Rep DisassembleArguments x)
-> (forall x. Rep DisassembleArguments x -> DisassembleArguments)
-> Generic DisassembleArguments
forall x. Rep DisassembleArguments x -> DisassembleArguments
forall x. DisassembleArguments -> Rep DisassembleArguments x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. DisassembleArguments -> Rep DisassembleArguments x
from :: forall x. DisassembleArguments -> Rep DisassembleArguments x
$cto :: forall x. Rep DisassembleArguments x -> DisassembleArguments
to :: forall x. Rep DisassembleArguments x -> DisassembleArguments
Generic)
instance FromJSON DisassembleArguments where
  parseJSON :: Value -> Parser DisassembleArguments
parseJSON = Value -> Parser DisassembleArguments
forall a.
(Generic a, GFromJSON Zero (Rep a), Typeable a) =>
Value -> Parser a
genericParseJSONWithModifier
data ColumnDescriptor
  = ColumnDescriptor
  { ColumnDescriptor -> String
columnDescriptorAttributeName :: String
    
    
    
  , ColumnDescriptor -> String
columnDescriptorLabel :: String
    
    
    
  , ColumnDescriptor -> Maybe String
columnDescriptorFormat :: Maybe String
    
    
    
    
  , ColumnDescriptor -> Maybe ColumnDescriptorType
columnDescriptorType :: Maybe ColumnDescriptorType
    
    
    
    
  , ColumnDescriptor -> Maybe Int
columnDescriptorWidth :: Maybe Int
    
    
    
  } deriving stock (Int -> ColumnDescriptor -> ShowS
[ColumnDescriptor] -> ShowS
ColumnDescriptor -> String
(Int -> ColumnDescriptor -> ShowS)
-> (ColumnDescriptor -> String)
-> ([ColumnDescriptor] -> ShowS)
-> Show ColumnDescriptor
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ColumnDescriptor -> ShowS
showsPrec :: Int -> ColumnDescriptor -> ShowS
$cshow :: ColumnDescriptor -> String
show :: ColumnDescriptor -> String
$cshowList :: [ColumnDescriptor] -> ShowS
showList :: [ColumnDescriptor] -> ShowS
Show, ColumnDescriptor -> ColumnDescriptor -> Bool
(ColumnDescriptor -> ColumnDescriptor -> Bool)
-> (ColumnDescriptor -> ColumnDescriptor -> Bool)
-> Eq ColumnDescriptor
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ColumnDescriptor -> ColumnDescriptor -> Bool
== :: ColumnDescriptor -> ColumnDescriptor -> Bool
$c/= :: ColumnDescriptor -> ColumnDescriptor -> Bool
/= :: ColumnDescriptor -> ColumnDescriptor -> Bool
Eq, (forall x. ColumnDescriptor -> Rep ColumnDescriptor x)
-> (forall x. Rep ColumnDescriptor x -> ColumnDescriptor)
-> Generic ColumnDescriptor
forall x. Rep ColumnDescriptor x -> ColumnDescriptor
forall x. ColumnDescriptor -> Rep ColumnDescriptor x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ColumnDescriptor -> Rep ColumnDescriptor x
from :: forall x. ColumnDescriptor -> Rep ColumnDescriptor x
$cto :: forall x. Rep ColumnDescriptor x -> ColumnDescriptor
to :: forall x. Rep ColumnDescriptor x -> ColumnDescriptor
Generic)
defaultColumnDescriptor :: ColumnDescriptor
defaultColumnDescriptor :: ColumnDescriptor
defaultColumnDescriptor
  = ColumnDescriptor
  { columnDescriptorAttributeName :: String
columnDescriptorAttributeName = String
forall a. Monoid a => a
mempty
  , columnDescriptorLabel :: String
columnDescriptorLabel = String
forall a. Monoid a => a
mempty
  , columnDescriptorFormat :: Maybe String
columnDescriptorFormat = Maybe String
forall a. Maybe a
Nothing
  , columnDescriptorType :: Maybe ColumnDescriptorType
columnDescriptorType = Maybe ColumnDescriptorType
forall a. Maybe a
Nothing
  , columnDescriptorWidth :: Maybe Int
columnDescriptorWidth = Maybe Int
forall a. Maybe a
Nothing
  }
instance ToJSON ColumnDescriptor where
  toJSON :: ColumnDescriptor -> Value
toJSON = ColumnDescriptor -> Value
forall a.
(Generic a, GToJSON Zero (Rep a), Typeable a) =>
a -> Value
genericToJSONWithModifier
data ColumnDescriptorType
  = ColumnDescriptorTypeString
  | ColumnDescriptorTypeInt
  | ColumnDescriptorTypeBool
  | ColumnDescriptorTypeUTCTime UTCTime
  deriving stock (Int -> ColumnDescriptorType -> ShowS
[ColumnDescriptorType] -> ShowS
ColumnDescriptorType -> String
(Int -> ColumnDescriptorType -> ShowS)
-> (ColumnDescriptorType -> String)
-> ([ColumnDescriptorType] -> ShowS)
-> Show ColumnDescriptorType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ColumnDescriptorType -> ShowS
showsPrec :: Int -> ColumnDescriptorType -> ShowS
$cshow :: ColumnDescriptorType -> String
show :: ColumnDescriptorType -> String
$cshowList :: [ColumnDescriptorType] -> ShowS
showList :: [ColumnDescriptorType] -> ShowS
Show, ColumnDescriptorType -> ColumnDescriptorType -> Bool
(ColumnDescriptorType -> ColumnDescriptorType -> Bool)
-> (ColumnDescriptorType -> ColumnDescriptorType -> Bool)
-> Eq ColumnDescriptorType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ColumnDescriptorType -> ColumnDescriptorType -> Bool
== :: ColumnDescriptorType -> ColumnDescriptorType -> Bool
$c/= :: ColumnDescriptorType -> ColumnDescriptorType -> Bool
/= :: ColumnDescriptorType -> ColumnDescriptorType -> Bool
Eq, (forall x. ColumnDescriptorType -> Rep ColumnDescriptorType x)
-> (forall x. Rep ColumnDescriptorType x -> ColumnDescriptorType)
-> Generic ColumnDescriptorType
forall x. Rep ColumnDescriptorType x -> ColumnDescriptorType
forall x. ColumnDescriptorType -> Rep ColumnDescriptorType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ColumnDescriptorType -> Rep ColumnDescriptorType x
from :: forall x. ColumnDescriptorType -> Rep ColumnDescriptorType x
$cto :: forall x. Rep ColumnDescriptorType x -> ColumnDescriptorType
to :: forall x. Rep ColumnDescriptorType x -> ColumnDescriptorType
Generic)
instance ToJSON ColumnDescriptorType where
  toJSON :: ColumnDescriptorType -> Value
toJSON (ColumnDescriptorTypeUTCTime UTCTime
utcTime) = UTCTime -> Value
forall a. ToJSON a => a -> Value
toJSON UTCTime
utcTime
  toJSON ColumnDescriptorType
typ = ColumnDescriptorType -> Value
forall a.
(Generic a, GToJSON Zero (Rep a), Typeable a) =>
a -> Value
genericToJSONWithModifier ColumnDescriptorType
typ
data ExceptionPathSegment
  = ExceptionPathSegment
  { ExceptionPathSegment -> Maybe Bool
exceptionPathSegmentNegate :: Maybe Bool
  , ExceptionPathSegment -> [String]
exceptionPathSegmentNames  :: [String]
  } deriving stock (Int -> ExceptionPathSegment -> ShowS
[ExceptionPathSegment] -> ShowS
ExceptionPathSegment -> String
(Int -> ExceptionPathSegment -> ShowS)
-> (ExceptionPathSegment -> String)
-> ([ExceptionPathSegment] -> ShowS)
-> Show ExceptionPathSegment
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ExceptionPathSegment -> ShowS
showsPrec :: Int -> ExceptionPathSegment -> ShowS
$cshow :: ExceptionPathSegment -> String
show :: ExceptionPathSegment -> String
$cshowList :: [ExceptionPathSegment] -> ShowS
showList :: [ExceptionPathSegment] -> ShowS
Show, ExceptionPathSegment -> ExceptionPathSegment -> Bool
(ExceptionPathSegment -> ExceptionPathSegment -> Bool)
-> (ExceptionPathSegment -> ExceptionPathSegment -> Bool)
-> Eq ExceptionPathSegment
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ExceptionPathSegment -> ExceptionPathSegment -> Bool
== :: ExceptionPathSegment -> ExceptionPathSegment -> Bool
$c/= :: ExceptionPathSegment -> ExceptionPathSegment -> Bool
/= :: ExceptionPathSegment -> ExceptionPathSegment -> Bool
Eq, (forall x. ExceptionPathSegment -> Rep ExceptionPathSegment x)
-> (forall x. Rep ExceptionPathSegment x -> ExceptionPathSegment)
-> Generic ExceptionPathSegment
forall x. Rep ExceptionPathSegment x -> ExceptionPathSegment
forall x. ExceptionPathSegment -> Rep ExceptionPathSegment x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ExceptionPathSegment -> Rep ExceptionPathSegment x
from :: forall x. ExceptionPathSegment -> Rep ExceptionPathSegment x
$cto :: forall x. Rep ExceptionPathSegment x -> ExceptionPathSegment
to :: forall x. Rep ExceptionPathSegment x -> ExceptionPathSegment
Generic)
instance FromJSON ExceptionPathSegment where
  parseJSON :: Value -> Parser ExceptionPathSegment
parseJSON = Value -> Parser ExceptionPathSegment
forall a.
(Generic a, GFromJSON Zero (Rep a), Typeable a) =>
Value -> Parser a
genericParseJSONWithModifier
data ModulesViewDescriptor
  = ModulesViewDescriptor
  { ModulesViewDescriptor -> [ColumnDescriptor]
modulesViewDescriptorColumns :: [ColumnDescriptor]
  } deriving stock (Int -> ModulesViewDescriptor -> ShowS
[ModulesViewDescriptor] -> ShowS
ModulesViewDescriptor -> String
(Int -> ModulesViewDescriptor -> ShowS)
-> (ModulesViewDescriptor -> String)
-> ([ModulesViewDescriptor] -> ShowS)
-> Show ModulesViewDescriptor
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ModulesViewDescriptor -> ShowS
showsPrec :: Int -> ModulesViewDescriptor -> ShowS
$cshow :: ModulesViewDescriptor -> String
show :: ModulesViewDescriptor -> String
$cshowList :: [ModulesViewDescriptor] -> ShowS
showList :: [ModulesViewDescriptor] -> ShowS
Show, ModulesViewDescriptor -> ModulesViewDescriptor -> Bool
(ModulesViewDescriptor -> ModulesViewDescriptor -> Bool)
-> (ModulesViewDescriptor -> ModulesViewDescriptor -> Bool)
-> Eq ModulesViewDescriptor
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ModulesViewDescriptor -> ModulesViewDescriptor -> Bool
== :: ModulesViewDescriptor -> ModulesViewDescriptor -> Bool
$c/= :: ModulesViewDescriptor -> ModulesViewDescriptor -> Bool
/= :: ModulesViewDescriptor -> ModulesViewDescriptor -> Bool
Eq, (forall x. ModulesViewDescriptor -> Rep ModulesViewDescriptor x)
-> (forall x. Rep ModulesViewDescriptor x -> ModulesViewDescriptor)
-> Generic ModulesViewDescriptor
forall x. Rep ModulesViewDescriptor x -> ModulesViewDescriptor
forall x. ModulesViewDescriptor -> Rep ModulesViewDescriptor x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ModulesViewDescriptor -> Rep ModulesViewDescriptor x
from :: forall x. ModulesViewDescriptor -> Rep ModulesViewDescriptor x
$cto :: forall x. Rep ModulesViewDescriptor x -> ModulesViewDescriptor
to :: forall x. Rep ModulesViewDescriptor x -> ModulesViewDescriptor
Generic)
instance ToJSON ModulesViewDescriptor where
  toJSON :: ModulesViewDescriptor -> Value
toJSON = ModulesViewDescriptor -> Value
forall a.
(Generic a, GToJSON Zero (Rep a), Typeable a) =>
a -> Value
genericToJSONWithModifier
defaultModulesViewDescriptor :: ModulesViewDescriptor
defaultModulesViewDescriptor :: ModulesViewDescriptor
defaultModulesViewDescriptor
  = ModulesViewDescriptor
  { modulesViewDescriptorColumns :: [ColumnDescriptor]
modulesViewDescriptorColumns = []
  }
data CompletionItemType
  = CompletionItemTypeMethod
  | CompletionItemTypeFunction
  | CompletionItemTypeConstructor
  | CompletionItemTypeField
  | CompletionItemTypeVariable
  | CompletionItemTypeClass
  | CompletionItemTypeInterface
  | CompletionItemTypeModule
  | CompletionItemTypeProperty
  | CompletionItemTypeUnit
  | CompletionItemTypeValue
  | CompletionItemTypeEnum
  | CompletionItemTypeKeyword
  | CompletionItemTypeSnippet
  | CompletionItemTypeText
  | CompletionItemTypeColor
  | CompletionItemTypeFile
  | CompletionItemTypeReference
  | CompletionItemTypeCustomcolor
  deriving stock (Int -> CompletionItemType -> ShowS
[CompletionItemType] -> ShowS
CompletionItemType -> String
(Int -> CompletionItemType -> ShowS)
-> (CompletionItemType -> String)
-> ([CompletionItemType] -> ShowS)
-> Show CompletionItemType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CompletionItemType -> ShowS
showsPrec :: Int -> CompletionItemType -> ShowS
$cshow :: CompletionItemType -> String
show :: CompletionItemType -> String
$cshowList :: [CompletionItemType] -> ShowS
showList :: [CompletionItemType] -> ShowS
Show, CompletionItemType -> CompletionItemType -> Bool
(CompletionItemType -> CompletionItemType -> Bool)
-> (CompletionItemType -> CompletionItemType -> Bool)
-> Eq CompletionItemType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CompletionItemType -> CompletionItemType -> Bool
== :: CompletionItemType -> CompletionItemType -> Bool
$c/= :: CompletionItemType -> CompletionItemType -> Bool
/= :: CompletionItemType -> CompletionItemType -> Bool
Eq, (forall x. CompletionItemType -> Rep CompletionItemType x)
-> (forall x. Rep CompletionItemType x -> CompletionItemType)
-> Generic CompletionItemType
forall x. Rep CompletionItemType x -> CompletionItemType
forall x. CompletionItemType -> Rep CompletionItemType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. CompletionItemType -> Rep CompletionItemType x
from :: forall x. CompletionItemType -> Rep CompletionItemType x
$cto :: forall x. Rep CompletionItemType x -> CompletionItemType
to :: forall x. Rep CompletionItemType x -> CompletionItemType
Generic)
data ExceptionBreakpointsFilter
  = ExceptionBreakpointsFilter
  { ExceptionBreakpointsFilter -> Text
exceptionBreakpointsFilterFilter :: Text
    
    
    
    
  , ExceptionBreakpointsFilter -> Text
exceptionBreakpointsFilterLabel :: Text
    
    
    
  , ExceptionBreakpointsFilter -> Maybe Text
exceptionBreakpointsFilterDescription :: Maybe Text
    
    
    
    
  , ExceptionBreakpointsFilter -> Maybe Bool
exceptionBreakpointsFilterDefault :: Maybe Bool
    
    
    
    
  , ExceptionBreakpointsFilter -> Maybe Bool
exceptionBreakpointsFilterSupportsCondition :: Maybe Bool
    
    
    
    
  , ExceptionBreakpointsFilter -> Maybe Text
exceptionBreakpointsFilterConditionDescription :: Maybe Text
    
    
    
    
  } deriving stock (Int -> ExceptionBreakpointsFilter -> ShowS
[ExceptionBreakpointsFilter] -> ShowS
ExceptionBreakpointsFilter -> String
(Int -> ExceptionBreakpointsFilter -> ShowS)
-> (ExceptionBreakpointsFilter -> String)
-> ([ExceptionBreakpointsFilter] -> ShowS)
-> Show ExceptionBreakpointsFilter
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ExceptionBreakpointsFilter -> ShowS
showsPrec :: Int -> ExceptionBreakpointsFilter -> ShowS
$cshow :: ExceptionBreakpointsFilter -> String
show :: ExceptionBreakpointsFilter -> String
$cshowList :: [ExceptionBreakpointsFilter] -> ShowS
showList :: [ExceptionBreakpointsFilter] -> ShowS
Show, ExceptionBreakpointsFilter -> ExceptionBreakpointsFilter -> Bool
(ExceptionBreakpointsFilter -> ExceptionBreakpointsFilter -> Bool)
-> (ExceptionBreakpointsFilter
    -> ExceptionBreakpointsFilter -> Bool)
-> Eq ExceptionBreakpointsFilter
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ExceptionBreakpointsFilter -> ExceptionBreakpointsFilter -> Bool
== :: ExceptionBreakpointsFilter -> ExceptionBreakpointsFilter -> Bool
$c/= :: ExceptionBreakpointsFilter -> ExceptionBreakpointsFilter -> Bool
/= :: ExceptionBreakpointsFilter -> ExceptionBreakpointsFilter -> Bool
Eq, (forall x.
 ExceptionBreakpointsFilter -> Rep ExceptionBreakpointsFilter x)
-> (forall x.
    Rep ExceptionBreakpointsFilter x -> ExceptionBreakpointsFilter)
-> Generic ExceptionBreakpointsFilter
forall x.
Rep ExceptionBreakpointsFilter x -> ExceptionBreakpointsFilter
forall x.
ExceptionBreakpointsFilter -> Rep ExceptionBreakpointsFilter x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x.
ExceptionBreakpointsFilter -> Rep ExceptionBreakpointsFilter x
from :: forall x.
ExceptionBreakpointsFilter -> Rep ExceptionBreakpointsFilter x
$cto :: forall x.
Rep ExceptionBreakpointsFilter x -> ExceptionBreakpointsFilter
to :: forall x.
Rep ExceptionBreakpointsFilter x -> ExceptionBreakpointsFilter
Generic)
defaultExceptionBreakpointsFilter :: ExceptionBreakpointsFilter
defaultExceptionBreakpointsFilter :: ExceptionBreakpointsFilter
defaultExceptionBreakpointsFilter
  = ExceptionBreakpointsFilter
  { exceptionBreakpointsFilterFilter :: Text
exceptionBreakpointsFilterFilter = Text
forall a. Monoid a => a
mempty
  , exceptionBreakpointsFilterLabel :: Text
exceptionBreakpointsFilterLabel = Text
forall a. Monoid a => a
mempty
  , exceptionBreakpointsFilterDescription :: Maybe Text
exceptionBreakpointsFilterDescription = Maybe Text
forall a. Maybe a
Nothing
  , exceptionBreakpointsFilterDefault :: Maybe Bool
exceptionBreakpointsFilterDefault = Maybe Bool
forall a. Maybe a
Nothing
  , exceptionBreakpointsFilterSupportsCondition :: Maybe Bool
exceptionBreakpointsFilterSupportsCondition = Maybe Bool
forall a. Maybe a
Nothing
  , exceptionBreakpointsFilterConditionDescription :: Maybe Text
exceptionBreakpointsFilterConditionDescription = Maybe Text
forall a. Maybe a
Nothing
  }
instance ToJSON ExceptionBreakpointsFilter where
  toJSON :: ExceptionBreakpointsFilter -> Value
toJSON = ExceptionBreakpointsFilter -> Value
forall a.
(Generic a, GToJSON Zero (Rep a), Typeable a) =>
a -> Value
genericToJSONWithModifier
data ConfigurationDoneArguments = ConfigurationDoneArguments
  deriving stock (Int -> ConfigurationDoneArguments -> ShowS
[ConfigurationDoneArguments] -> ShowS
ConfigurationDoneArguments -> String
(Int -> ConfigurationDoneArguments -> ShowS)
-> (ConfigurationDoneArguments -> String)
-> ([ConfigurationDoneArguments] -> ShowS)
-> Show ConfigurationDoneArguments
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ConfigurationDoneArguments -> ShowS
showsPrec :: Int -> ConfigurationDoneArguments -> ShowS
$cshow :: ConfigurationDoneArguments -> String
show :: ConfigurationDoneArguments -> String
$cshowList :: [ConfigurationDoneArguments] -> ShowS
showList :: [ConfigurationDoneArguments] -> ShowS
Show, ConfigurationDoneArguments -> ConfigurationDoneArguments -> Bool
(ConfigurationDoneArguments -> ConfigurationDoneArguments -> Bool)
-> (ConfigurationDoneArguments
    -> ConfigurationDoneArguments -> Bool)
-> Eq ConfigurationDoneArguments
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ConfigurationDoneArguments -> ConfigurationDoneArguments -> Bool
== :: ConfigurationDoneArguments -> ConfigurationDoneArguments -> Bool
$c/= :: ConfigurationDoneArguments -> ConfigurationDoneArguments -> Bool
/= :: ConfigurationDoneArguments -> ConfigurationDoneArguments -> Bool
Eq)
instance FromJSON ConfigurationDoneArguments where
   parseJSON :: Value -> Parser ConfigurationDoneArguments
parseJSON Value
_ = ConfigurationDoneArguments -> Parser ConfigurationDoneArguments
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ConfigurationDoneArguments
ConfigurationDoneArguments
data ThreadsArguments = ThreadsArguments
  deriving stock (Int -> ThreadsArguments -> ShowS
[ThreadsArguments] -> ShowS
ThreadsArguments -> String
(Int -> ThreadsArguments -> ShowS)
-> (ThreadsArguments -> String)
-> ([ThreadsArguments] -> ShowS)
-> Show ThreadsArguments
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ThreadsArguments -> ShowS
showsPrec :: Int -> ThreadsArguments -> ShowS
$cshow :: ThreadsArguments -> String
show :: ThreadsArguments -> String
$cshowList :: [ThreadsArguments] -> ShowS
showList :: [ThreadsArguments] -> ShowS
Show, ThreadsArguments -> ThreadsArguments -> Bool
(ThreadsArguments -> ThreadsArguments -> Bool)
-> (ThreadsArguments -> ThreadsArguments -> Bool)
-> Eq ThreadsArguments
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ThreadsArguments -> ThreadsArguments -> Bool
== :: ThreadsArguments -> ThreadsArguments -> Bool
$c/= :: ThreadsArguments -> ThreadsArguments -> Bool
/= :: ThreadsArguments -> ThreadsArguments -> Bool
Eq)
instance FromJSON ThreadsArguments where
   parseJSON :: Value -> Parser ThreadsArguments
parseJSON Value
_ = ThreadsArguments -> Parser ThreadsArguments
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ThreadsArguments
ThreadsArguments