{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# OPTIONS_GHC -fno-warn-unused-binds #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
module Network.Google.Debugger.Types.Product where
import Network.Google.Debugger.Types.Sum
import Network.Google.Prelude
newtype RegisterDebuggeeResponse = RegisterDebuggeeResponse'
{ _rdrDebuggee :: Maybe Debuggee
} deriving (Eq,Show,Data,Typeable,Generic)
registerDebuggeeResponse
:: RegisterDebuggeeResponse
registerDebuggeeResponse =
RegisterDebuggeeResponse'
{ _rdrDebuggee = Nothing
}
rdrDebuggee :: Lens' RegisterDebuggeeResponse (Maybe Debuggee)
rdrDebuggee
= lens _rdrDebuggee (\ s a -> s{_rdrDebuggee = a})
instance FromJSON RegisterDebuggeeResponse where
parseJSON
= withObject "RegisterDebuggeeResponse"
(\ o ->
RegisterDebuggeeResponse' <$> (o .:? "debuggee"))
instance ToJSON RegisterDebuggeeResponse where
toJSON RegisterDebuggeeResponse'{..}
= object
(catMaybes [("debuggee" .=) <$> _rdrDebuggee])
data SourceContext = SourceContext'
{ _scCloudWorkspace :: !(Maybe CloudWorkspaceSourceContext)
, _scCloudRepo :: !(Maybe CloudRepoSourceContext)
, _scGerrit :: !(Maybe GerritSourceContext)
, _scGit :: !(Maybe GitSourceContext)
} deriving (Eq,Show,Data,Typeable,Generic)
sourceContext
:: SourceContext
sourceContext =
SourceContext'
{ _scCloudWorkspace = Nothing
, _scCloudRepo = Nothing
, _scGerrit = Nothing
, _scGit = Nothing
}
scCloudWorkspace :: Lens' SourceContext (Maybe CloudWorkspaceSourceContext)
scCloudWorkspace
= lens _scCloudWorkspace
(\ s a -> s{_scCloudWorkspace = a})
scCloudRepo :: Lens' SourceContext (Maybe CloudRepoSourceContext)
scCloudRepo
= lens _scCloudRepo (\ s a -> s{_scCloudRepo = a})
scGerrit :: Lens' SourceContext (Maybe GerritSourceContext)
scGerrit = lens _scGerrit (\ s a -> s{_scGerrit = a})
scGit :: Lens' SourceContext (Maybe GitSourceContext)
scGit = lens _scGit (\ s a -> s{_scGit = a})
instance FromJSON SourceContext where
parseJSON
= withObject "SourceContext"
(\ o ->
SourceContext' <$>
(o .:? "cloudWorkspace") <*> (o .:? "cloudRepo") <*>
(o .:? "gerrit")
<*> (o .:? "git"))
instance ToJSON SourceContext where
toJSON SourceContext'{..}
= object
(catMaybes
[("cloudWorkspace" .=) <$> _scCloudWorkspace,
("cloudRepo" .=) <$> _scCloudRepo,
("gerrit" .=) <$> _scGerrit, ("git" .=) <$> _scGit])
newtype SetBreakpointResponse = SetBreakpointResponse'
{ _sbrBreakpoint :: Maybe Breakpoint
} deriving (Eq,Show,Data,Typeable,Generic)
setBreakpointResponse
:: SetBreakpointResponse
setBreakpointResponse =
SetBreakpointResponse'
{ _sbrBreakpoint = Nothing
}
sbrBreakpoint :: Lens' SetBreakpointResponse (Maybe Breakpoint)
sbrBreakpoint
= lens _sbrBreakpoint
(\ s a -> s{_sbrBreakpoint = a})
instance FromJSON SetBreakpointResponse where
parseJSON
= withObject "SetBreakpointResponse"
(\ o ->
SetBreakpointResponse' <$> (o .:? "breakpoint"))
instance ToJSON SetBreakpointResponse where
toJSON SetBreakpointResponse'{..}
= object
(catMaybes [("breakpoint" .=) <$> _sbrBreakpoint])
data Empty =
Empty'
deriving (Eq,Show,Data,Typeable,Generic)
empty
:: Empty
empty = Empty'
instance FromJSON Empty where
parseJSON = withObject "Empty" (\ o -> pure Empty')
instance ToJSON Empty where
toJSON = const emptyObject
data UpdateActiveBreakpointResponse =
UpdateActiveBreakpointResponse'
deriving (Eq,Show,Data,Typeable,Generic)
updateActiveBreakpointResponse
:: UpdateActiveBreakpointResponse
updateActiveBreakpointResponse = UpdateActiveBreakpointResponse'
instance FromJSON UpdateActiveBreakpointResponse
where
parseJSON
= withObject "UpdateActiveBreakpointResponse"
(\ o -> pure UpdateActiveBreakpointResponse')
instance ToJSON UpdateActiveBreakpointResponse where
toJSON = const emptyObject
data GerritSourceContext = GerritSourceContext'
{ _gscGerritProject :: !(Maybe Text)
, _gscAliasName :: !(Maybe Text)
, _gscRevisionId :: !(Maybe Text)
, _gscHostURI :: !(Maybe Text)
, _gscAliasContext :: !(Maybe AliasContext)
} deriving (Eq,Show,Data,Typeable,Generic)
gerritSourceContext
:: GerritSourceContext
gerritSourceContext =
GerritSourceContext'
{ _gscGerritProject = Nothing
, _gscAliasName = Nothing
, _gscRevisionId = Nothing
, _gscHostURI = Nothing
, _gscAliasContext = Nothing
}
gscGerritProject :: Lens' GerritSourceContext (Maybe Text)
gscGerritProject
= lens _gscGerritProject
(\ s a -> s{_gscGerritProject = a})
gscAliasName :: Lens' GerritSourceContext (Maybe Text)
gscAliasName
= lens _gscAliasName (\ s a -> s{_gscAliasName = a})
gscRevisionId :: Lens' GerritSourceContext (Maybe Text)
gscRevisionId
= lens _gscRevisionId
(\ s a -> s{_gscRevisionId = a})
gscHostURI :: Lens' GerritSourceContext (Maybe Text)
gscHostURI
= lens _gscHostURI (\ s a -> s{_gscHostURI = a})
gscAliasContext :: Lens' GerritSourceContext (Maybe AliasContext)
gscAliasContext
= lens _gscAliasContext
(\ s a -> s{_gscAliasContext = a})
instance FromJSON GerritSourceContext where
parseJSON
= withObject "GerritSourceContext"
(\ o ->
GerritSourceContext' <$>
(o .:? "gerritProject") <*> (o .:? "aliasName") <*>
(o .:? "revisionId")
<*> (o .:? "hostUri")
<*> (o .:? "aliasContext"))
instance ToJSON GerritSourceContext where
toJSON GerritSourceContext'{..}
= object
(catMaybes
[("gerritProject" .=) <$> _gscGerritProject,
("aliasName" .=) <$> _gscAliasName,
("revisionId" .=) <$> _gscRevisionId,
("hostUri" .=) <$> _gscHostURI,
("aliasContext" .=) <$> _gscAliasContext])
data RepoId = RepoId'
{ _riUid :: !(Maybe Text)
, _riProjectRepoId :: !(Maybe ProjectRepoId)
} deriving (Eq,Show,Data,Typeable,Generic)
repoId
:: RepoId
repoId =
RepoId'
{ _riUid = Nothing
, _riProjectRepoId = Nothing
}
riUid :: Lens' RepoId (Maybe Text)
riUid = lens _riUid (\ s a -> s{_riUid = a})
riProjectRepoId :: Lens' RepoId (Maybe ProjectRepoId)
riProjectRepoId
= lens _riProjectRepoId
(\ s a -> s{_riProjectRepoId = a})
instance FromJSON RepoId where
parseJSON
= withObject "RepoId"
(\ o ->
RepoId' <$>
(o .:? "uid") <*> (o .:? "projectRepoId"))
instance ToJSON RepoId where
toJSON RepoId'{..}
= object
(catMaybes
[("uid" .=) <$> _riUid,
("projectRepoId" .=) <$> _riProjectRepoId])
newtype ExtendedSourceContextLabels = ExtendedSourceContextLabels'
{ _esclAddtional :: HashMap Text Text
} deriving (Eq,Show,Data,Typeable,Generic)
extendedSourceContextLabels
:: HashMap Text Text
-> ExtendedSourceContextLabels
extendedSourceContextLabels pEsclAddtional_ =
ExtendedSourceContextLabels'
{ _esclAddtional = _Coerce # pEsclAddtional_
}
esclAddtional :: Lens' ExtendedSourceContextLabels (HashMap Text Text)
esclAddtional
= lens _esclAddtional
(\ s a -> s{_esclAddtional = a})
. _Coerce
instance FromJSON ExtendedSourceContextLabels where
parseJSON
= withObject "ExtendedSourceContextLabels"
(\ o ->
ExtendedSourceContextLabels' <$> (parseJSONObject o))
instance ToJSON ExtendedSourceContextLabels where
toJSON = toJSON . _esclAddtional
data ProjectRepoId = ProjectRepoId'
{ _priRepoName :: !(Maybe Text)
, _priProjectId :: !(Maybe Text)
} deriving (Eq,Show,Data,Typeable,Generic)
projectRepoId
:: ProjectRepoId
projectRepoId =
ProjectRepoId'
{ _priRepoName = Nothing
, _priProjectId = Nothing
}
priRepoName :: Lens' ProjectRepoId (Maybe Text)
priRepoName
= lens _priRepoName (\ s a -> s{_priRepoName = a})
priProjectId :: Lens' ProjectRepoId (Maybe Text)
priProjectId
= lens _priProjectId (\ s a -> s{_priProjectId = a})
instance FromJSON ProjectRepoId where
parseJSON
= withObject "ProjectRepoId"
(\ o ->
ProjectRepoId' <$>
(o .:? "repoName") <*> (o .:? "projectId"))
instance ToJSON ProjectRepoId where
toJSON ProjectRepoId'{..}
= object
(catMaybes
[("repoName" .=) <$> _priRepoName,
("projectId" .=) <$> _priProjectId])
data FormatMessage = FormatMessage'
{ _fmFormat :: !(Maybe Text)
, _fmParameters :: !(Maybe [Text])
} deriving (Eq,Show,Data,Typeable,Generic)
formatMessage
:: FormatMessage
formatMessage =
FormatMessage'
{ _fmFormat = Nothing
, _fmParameters = Nothing
}
fmFormat :: Lens' FormatMessage (Maybe Text)
fmFormat = lens _fmFormat (\ s a -> s{_fmFormat = a})
fmParameters :: Lens' FormatMessage [Text]
fmParameters
= lens _fmParameters (\ s a -> s{_fmParameters = a})
. _Default
. _Coerce
instance FromJSON FormatMessage where
parseJSON
= withObject "FormatMessage"
(\ o ->
FormatMessage' <$>
(o .:? "format") <*> (o .:? "parameters" .!= mempty))
instance ToJSON FormatMessage where
toJSON FormatMessage'{..}
= object
(catMaybes
[("format" .=) <$> _fmFormat,
("parameters" .=) <$> _fmParameters])
data Breakpoint = Breakpoint'
{ _bStatus :: !(Maybe StatusMessage)
, _bLogLevel :: !(Maybe BreakpointLogLevel)
, _bLocation :: !(Maybe SourceLocation)
, _bAction :: !(Maybe BreakpointAction)
, _bFinalTime :: !(Maybe DateTime')
, _bExpressions :: !(Maybe [Text])
, _bLogMessageFormat :: !(Maybe Text)
, _bId :: !(Maybe Text)
, _bLabels :: !(Maybe BreakpointLabels)
, _bUserEmail :: !(Maybe Text)
, _bVariableTable :: !(Maybe [Variable])
, _bStackFrames :: !(Maybe [StackFrame])
, _bCondition :: !(Maybe Text)
, _bEvaluatedExpressions :: !(Maybe [Variable])
, _bCreateTime :: !(Maybe DateTime')
, _bIsFinalState :: !(Maybe Bool)
} deriving (Eq,Show,Data,Typeable,Generic)
breakpoint
:: Breakpoint
breakpoint =
Breakpoint'
{ _bStatus = Nothing
, _bLogLevel = Nothing
, _bLocation = Nothing
, _bAction = Nothing
, _bFinalTime = Nothing
, _bExpressions = Nothing
, _bLogMessageFormat = Nothing
, _bId = Nothing
, _bLabels = Nothing
, _bUserEmail = Nothing
, _bVariableTable = Nothing
, _bStackFrames = Nothing
, _bCondition = Nothing
, _bEvaluatedExpressions = Nothing
, _bCreateTime = Nothing
, _bIsFinalState = Nothing
}
bStatus :: Lens' Breakpoint (Maybe StatusMessage)
bStatus = lens _bStatus (\ s a -> s{_bStatus = a})
bLogLevel :: Lens' Breakpoint (Maybe BreakpointLogLevel)
bLogLevel
= lens _bLogLevel (\ s a -> s{_bLogLevel = a})
bLocation :: Lens' Breakpoint (Maybe SourceLocation)
bLocation
= lens _bLocation (\ s a -> s{_bLocation = a})
bAction :: Lens' Breakpoint (Maybe BreakpointAction)
bAction = lens _bAction (\ s a -> s{_bAction = a})
bFinalTime :: Lens' Breakpoint (Maybe UTCTime)
bFinalTime
= lens _bFinalTime (\ s a -> s{_bFinalTime = a}) .
mapping _DateTime
bExpressions :: Lens' Breakpoint [Text]
bExpressions
= lens _bExpressions (\ s a -> s{_bExpressions = a})
. _Default
. _Coerce
bLogMessageFormat :: Lens' Breakpoint (Maybe Text)
bLogMessageFormat
= lens _bLogMessageFormat
(\ s a -> s{_bLogMessageFormat = a})
bId :: Lens' Breakpoint (Maybe Text)
bId = lens _bId (\ s a -> s{_bId = a})
bLabels :: Lens' Breakpoint (Maybe BreakpointLabels)
bLabels = lens _bLabels (\ s a -> s{_bLabels = a})
bUserEmail :: Lens' Breakpoint (Maybe Text)
bUserEmail
= lens _bUserEmail (\ s a -> s{_bUserEmail = a})
bVariableTable :: Lens' Breakpoint [Variable]
bVariableTable
= lens _bVariableTable
(\ s a -> s{_bVariableTable = a})
. _Default
. _Coerce
bStackFrames :: Lens' Breakpoint [StackFrame]
bStackFrames
= lens _bStackFrames (\ s a -> s{_bStackFrames = a})
. _Default
. _Coerce
bCondition :: Lens' Breakpoint (Maybe Text)
bCondition
= lens _bCondition (\ s a -> s{_bCondition = a})
bEvaluatedExpressions :: Lens' Breakpoint [Variable]
bEvaluatedExpressions
= lens _bEvaluatedExpressions
(\ s a -> s{_bEvaluatedExpressions = a})
. _Default
. _Coerce
bCreateTime :: Lens' Breakpoint (Maybe UTCTime)
bCreateTime
= lens _bCreateTime (\ s a -> s{_bCreateTime = a}) .
mapping _DateTime
bIsFinalState :: Lens' Breakpoint (Maybe Bool)
bIsFinalState
= lens _bIsFinalState
(\ s a -> s{_bIsFinalState = a})
instance FromJSON Breakpoint where
parseJSON
= withObject "Breakpoint"
(\ o ->
Breakpoint' <$>
(o .:? "status") <*> (o .:? "logLevel") <*>
(o .:? "location")
<*> (o .:? "action")
<*> (o .:? "finalTime")
<*> (o .:? "expressions" .!= mempty)
<*> (o .:? "logMessageFormat")
<*> (o .:? "id")
<*> (o .:? "labels")
<*> (o .:? "userEmail")
<*> (o .:? "variableTable" .!= mempty)
<*> (o .:? "stackFrames" .!= mempty)
<*> (o .:? "condition")
<*> (o .:? "evaluatedExpressions" .!= mempty)
<*> (o .:? "createTime")
<*> (o .:? "isFinalState"))
instance ToJSON Breakpoint where
toJSON Breakpoint'{..}
= object
(catMaybes
[("status" .=) <$> _bStatus,
("logLevel" .=) <$> _bLogLevel,
("location" .=) <$> _bLocation,
("action" .=) <$> _bAction,
("finalTime" .=) <$> _bFinalTime,
("expressions" .=) <$> _bExpressions,
("logMessageFormat" .=) <$> _bLogMessageFormat,
("id" .=) <$> _bId, ("labels" .=) <$> _bLabels,
("userEmail" .=) <$> _bUserEmail,
("variableTable" .=) <$> _bVariableTable,
("stackFrames" .=) <$> _bStackFrames,
("condition" .=) <$> _bCondition,
("evaluatedExpressions" .=) <$>
_bEvaluatedExpressions,
("createTime" .=) <$> _bCreateTime,
("isFinalState" .=) <$> _bIsFinalState])
newtype BreakpointLabels = BreakpointLabels'
{ _blAddtional :: HashMap Text Text
} deriving (Eq,Show,Data,Typeable,Generic)
breakpointLabels
:: HashMap Text Text
-> BreakpointLabels
breakpointLabels pBlAddtional_ =
BreakpointLabels'
{ _blAddtional = _Coerce # pBlAddtional_
}
blAddtional :: Lens' BreakpointLabels (HashMap Text Text)
blAddtional
= lens _blAddtional (\ s a -> s{_blAddtional = a}) .
_Coerce
instance FromJSON BreakpointLabels where
parseJSON
= withObject "BreakpointLabels"
(\ o -> BreakpointLabels' <$> (parseJSONObject o))
instance ToJSON BreakpointLabels where
toJSON = toJSON . _blAddtional
newtype GetBreakpointResponse = GetBreakpointResponse'
{ _gbrBreakpoint :: Maybe Breakpoint
} deriving (Eq,Show,Data,Typeable,Generic)
getBreakpointResponse
:: GetBreakpointResponse
getBreakpointResponse =
GetBreakpointResponse'
{ _gbrBreakpoint = Nothing
}
gbrBreakpoint :: Lens' GetBreakpointResponse (Maybe Breakpoint)
gbrBreakpoint
= lens _gbrBreakpoint
(\ s a -> s{_gbrBreakpoint = a})
instance FromJSON GetBreakpointResponse where
parseJSON
= withObject "GetBreakpointResponse"
(\ o ->
GetBreakpointResponse' <$> (o .:? "breakpoint"))
instance ToJSON GetBreakpointResponse where
toJSON GetBreakpointResponse'{..}
= object
(catMaybes [("breakpoint" .=) <$> _gbrBreakpoint])
data Variable = Variable'
{ _vStatus :: !(Maybe StatusMessage)
, _vVarTableIndex :: !(Maybe (Textual Int32))
, _vMembers :: !(Maybe [Variable])
, _vValue :: !(Maybe Text)
, _vName :: !(Maybe Text)
, _vType :: !(Maybe Text)
} deriving (Eq,Show,Data,Typeable,Generic)
variable
:: Variable
variable =
Variable'
{ _vStatus = Nothing
, _vVarTableIndex = Nothing
, _vMembers = Nothing
, _vValue = Nothing
, _vName = Nothing
, _vType = Nothing
}
vStatus :: Lens' Variable (Maybe StatusMessage)
vStatus = lens _vStatus (\ s a -> s{_vStatus = a})
vVarTableIndex :: Lens' Variable (Maybe Int32)
vVarTableIndex
= lens _vVarTableIndex
(\ s a -> s{_vVarTableIndex = a})
. mapping _Coerce
vMembers :: Lens' Variable [Variable]
vMembers
= lens _vMembers (\ s a -> s{_vMembers = a}) .
_Default
. _Coerce
vValue :: Lens' Variable (Maybe Text)
vValue = lens _vValue (\ s a -> s{_vValue = a})
vName :: Lens' Variable (Maybe Text)
vName = lens _vName (\ s a -> s{_vName = a})
vType :: Lens' Variable (Maybe Text)
vType = lens _vType (\ s a -> s{_vType = a})
instance FromJSON Variable where
parseJSON
= withObject "Variable"
(\ o ->
Variable' <$>
(o .:? "status") <*> (o .:? "varTableIndex") <*>
(o .:? "members" .!= mempty)
<*> (o .:? "value")
<*> (o .:? "name")
<*> (o .:? "type"))
instance ToJSON Variable where
toJSON Variable'{..}
= object
(catMaybes
[("status" .=) <$> _vStatus,
("varTableIndex" .=) <$> _vVarTableIndex,
("members" .=) <$> _vMembers,
("value" .=) <$> _vValue, ("name" .=) <$> _vName,
("type" .=) <$> _vType])
data ListBreakpointsResponse = ListBreakpointsResponse'
{ _lbrNextWaitToken :: !(Maybe Text)
, _lbrBreakpoints :: !(Maybe [Breakpoint])
} deriving (Eq,Show,Data,Typeable,Generic)
listBreakpointsResponse
:: ListBreakpointsResponse
listBreakpointsResponse =
ListBreakpointsResponse'
{ _lbrNextWaitToken = Nothing
, _lbrBreakpoints = Nothing
}
lbrNextWaitToken :: Lens' ListBreakpointsResponse (Maybe Text)
lbrNextWaitToken
= lens _lbrNextWaitToken
(\ s a -> s{_lbrNextWaitToken = a})
lbrBreakpoints :: Lens' ListBreakpointsResponse [Breakpoint]
lbrBreakpoints
= lens _lbrBreakpoints
(\ s a -> s{_lbrBreakpoints = a})
. _Default
. _Coerce
instance FromJSON ListBreakpointsResponse where
parseJSON
= withObject "ListBreakpointsResponse"
(\ o ->
ListBreakpointsResponse' <$>
(o .:? "nextWaitToken") <*>
(o .:? "breakpoints" .!= mempty))
instance ToJSON ListBreakpointsResponse where
toJSON ListBreakpointsResponse'{..}
= object
(catMaybes
[("nextWaitToken" .=) <$> _lbrNextWaitToken,
("breakpoints" .=) <$> _lbrBreakpoints])
newtype ListDebuggeesResponse = ListDebuggeesResponse'
{ _ldrDebuggees :: Maybe [Debuggee]
} deriving (Eq,Show,Data,Typeable,Generic)
listDebuggeesResponse
:: ListDebuggeesResponse
listDebuggeesResponse =
ListDebuggeesResponse'
{ _ldrDebuggees = Nothing
}
ldrDebuggees :: Lens' ListDebuggeesResponse [Debuggee]
ldrDebuggees
= lens _ldrDebuggees (\ s a -> s{_ldrDebuggees = a})
. _Default
. _Coerce
instance FromJSON ListDebuggeesResponse where
parseJSON
= withObject "ListDebuggeesResponse"
(\ o ->
ListDebuggeesResponse' <$>
(o .:? "debuggees" .!= mempty))
instance ToJSON ListDebuggeesResponse where
toJSON ListDebuggeesResponse'{..}
= object
(catMaybes [("debuggees" .=) <$> _ldrDebuggees])
newtype UpdateActiveBreakpointRequest = UpdateActiveBreakpointRequest'
{ _uabrBreakpoint :: Maybe Breakpoint
} deriving (Eq,Show,Data,Typeable,Generic)
updateActiveBreakpointRequest
:: UpdateActiveBreakpointRequest
updateActiveBreakpointRequest =
UpdateActiveBreakpointRequest'
{ _uabrBreakpoint = Nothing
}
uabrBreakpoint :: Lens' UpdateActiveBreakpointRequest (Maybe Breakpoint)
uabrBreakpoint
= lens _uabrBreakpoint
(\ s a -> s{_uabrBreakpoint = a})
instance FromJSON UpdateActiveBreakpointRequest where
parseJSON
= withObject "UpdateActiveBreakpointRequest"
(\ o ->
UpdateActiveBreakpointRequest' <$>
(o .:? "breakpoint"))
instance ToJSON UpdateActiveBreakpointRequest where
toJSON UpdateActiveBreakpointRequest'{..}
= object
(catMaybes [("breakpoint" .=) <$> _uabrBreakpoint])
data StatusMessage = StatusMessage'
{ _smRefersTo :: !(Maybe StatusMessageRefersTo)
, _smIsError :: !(Maybe Bool)
, _smDescription :: !(Maybe FormatMessage)
} deriving (Eq,Show,Data,Typeable,Generic)
statusMessage
:: StatusMessage
statusMessage =
StatusMessage'
{ _smRefersTo = Nothing
, _smIsError = Nothing
, _smDescription = Nothing
}
smRefersTo :: Lens' StatusMessage (Maybe StatusMessageRefersTo)
smRefersTo
= lens _smRefersTo (\ s a -> s{_smRefersTo = a})
smIsError :: Lens' StatusMessage (Maybe Bool)
smIsError
= lens _smIsError (\ s a -> s{_smIsError = a})
smDescription :: Lens' StatusMessage (Maybe FormatMessage)
smDescription
= lens _smDescription
(\ s a -> s{_smDescription = a})
instance FromJSON StatusMessage where
parseJSON
= withObject "StatusMessage"
(\ o ->
StatusMessage' <$>
(o .:? "refersTo") <*> (o .:? "isError") <*>
(o .:? "description"))
instance ToJSON StatusMessage where
toJSON StatusMessage'{..}
= object
(catMaybes
[("refersTo" .=) <$> _smRefersTo,
("isError" .=) <$> _smIsError,
("description" .=) <$> _smDescription])
data ListActiveBreakpointsResponse = ListActiveBreakpointsResponse'
{ _labrNextWaitToken :: !(Maybe Text)
, _labrBreakpoints :: !(Maybe [Breakpoint])
, _labrWaitExpired :: !(Maybe Bool)
} deriving (Eq,Show,Data,Typeable,Generic)
listActiveBreakpointsResponse
:: ListActiveBreakpointsResponse
listActiveBreakpointsResponse =
ListActiveBreakpointsResponse'
{ _labrNextWaitToken = Nothing
, _labrBreakpoints = Nothing
, _labrWaitExpired = Nothing
}
labrNextWaitToken :: Lens' ListActiveBreakpointsResponse (Maybe Text)
labrNextWaitToken
= lens _labrNextWaitToken
(\ s a -> s{_labrNextWaitToken = a})
labrBreakpoints :: Lens' ListActiveBreakpointsResponse [Breakpoint]
labrBreakpoints
= lens _labrBreakpoints
(\ s a -> s{_labrBreakpoints = a})
. _Default
. _Coerce
labrWaitExpired :: Lens' ListActiveBreakpointsResponse (Maybe Bool)
labrWaitExpired
= lens _labrWaitExpired
(\ s a -> s{_labrWaitExpired = a})
instance FromJSON ListActiveBreakpointsResponse where
parseJSON
= withObject "ListActiveBreakpointsResponse"
(\ o ->
ListActiveBreakpointsResponse' <$>
(o .:? "nextWaitToken") <*>
(o .:? "breakpoints" .!= mempty)
<*> (o .:? "waitExpired"))
instance ToJSON ListActiveBreakpointsResponse where
toJSON ListActiveBreakpointsResponse'{..}
= object
(catMaybes
[("nextWaitToken" .=) <$> _labrNextWaitToken,
("breakpoints" .=) <$> _labrBreakpoints,
("waitExpired" .=) <$> _labrWaitExpired])
data ExtendedSourceContext = ExtendedSourceContext'
{ _escContext :: !(Maybe SourceContext)
, _escLabels :: !(Maybe ExtendedSourceContextLabels)
} deriving (Eq,Show,Data,Typeable,Generic)
extendedSourceContext
:: ExtendedSourceContext
extendedSourceContext =
ExtendedSourceContext'
{ _escContext = Nothing
, _escLabels = Nothing
}
escContext :: Lens' ExtendedSourceContext (Maybe SourceContext)
escContext
= lens _escContext (\ s a -> s{_escContext = a})
escLabels :: Lens' ExtendedSourceContext (Maybe ExtendedSourceContextLabels)
escLabels
= lens _escLabels (\ s a -> s{_escLabels = a})
instance FromJSON ExtendedSourceContext where
parseJSON
= withObject "ExtendedSourceContext"
(\ o ->
ExtendedSourceContext' <$>
(o .:? "context") <*> (o .:? "labels"))
instance ToJSON ExtendedSourceContext where
toJSON ExtendedSourceContext'{..}
= object
(catMaybes
[("context" .=) <$> _escContext,
("labels" .=) <$> _escLabels])
data GitSourceContext = GitSourceContext'
{ _gURL :: !(Maybe Text)
, _gRevisionId :: !(Maybe Text)
} deriving (Eq,Show,Data,Typeable,Generic)
gitSourceContext
:: GitSourceContext
gitSourceContext =
GitSourceContext'
{ _gURL = Nothing
, _gRevisionId = Nothing
}
gURL :: Lens' GitSourceContext (Maybe Text)
gURL = lens _gURL (\ s a -> s{_gURL = a})
gRevisionId :: Lens' GitSourceContext (Maybe Text)
gRevisionId
= lens _gRevisionId (\ s a -> s{_gRevisionId = a})
instance FromJSON GitSourceContext where
parseJSON
= withObject "GitSourceContext"
(\ o ->
GitSourceContext' <$>
(o .:? "url") <*> (o .:? "revisionId"))
instance ToJSON GitSourceContext where
toJSON GitSourceContext'{..}
= object
(catMaybes
[("url" .=) <$> _gURL,
("revisionId" .=) <$> _gRevisionId])
data SourceLocation = SourceLocation'
{ _slPath :: !(Maybe Text)
, _slLine :: !(Maybe (Textual Int32))
, _slColumn :: !(Maybe (Textual Int32))
} deriving (Eq,Show,Data,Typeable,Generic)
sourceLocation
:: SourceLocation
sourceLocation =
SourceLocation'
{ _slPath = Nothing
, _slLine = Nothing
, _slColumn = Nothing
}
slPath :: Lens' SourceLocation (Maybe Text)
slPath = lens _slPath (\ s a -> s{_slPath = a})
slLine :: Lens' SourceLocation (Maybe Int32)
slLine
= lens _slLine (\ s a -> s{_slLine = a}) .
mapping _Coerce
slColumn :: Lens' SourceLocation (Maybe Int32)
slColumn
= lens _slColumn (\ s a -> s{_slColumn = a}) .
mapping _Coerce
instance FromJSON SourceLocation where
parseJSON
= withObject "SourceLocation"
(\ o ->
SourceLocation' <$>
(o .:? "path") <*> (o .:? "line") <*>
(o .:? "column"))
instance ToJSON SourceLocation where
toJSON SourceLocation'{..}
= object
(catMaybes
[("path" .=) <$> _slPath, ("line" .=) <$> _slLine,
("column" .=) <$> _slColumn])
data StackFrame = StackFrame'
{ _sfFunction :: !(Maybe Text)
, _sfLocation :: !(Maybe SourceLocation)
, _sfArguments :: !(Maybe [Variable])
, _sfLocals :: !(Maybe [Variable])
} deriving (Eq,Show,Data,Typeable,Generic)
stackFrame
:: StackFrame
stackFrame =
StackFrame'
{ _sfFunction = Nothing
, _sfLocation = Nothing
, _sfArguments = Nothing
, _sfLocals = Nothing
}
sfFunction :: Lens' StackFrame (Maybe Text)
sfFunction
= lens _sfFunction (\ s a -> s{_sfFunction = a})
sfLocation :: Lens' StackFrame (Maybe SourceLocation)
sfLocation
= lens _sfLocation (\ s a -> s{_sfLocation = a})
sfArguments :: Lens' StackFrame [Variable]
sfArguments
= lens _sfArguments (\ s a -> s{_sfArguments = a}) .
_Default
. _Coerce
sfLocals :: Lens' StackFrame [Variable]
sfLocals
= lens _sfLocals (\ s a -> s{_sfLocals = a}) .
_Default
. _Coerce
instance FromJSON StackFrame where
parseJSON
= withObject "StackFrame"
(\ o ->
StackFrame' <$>
(o .:? "function") <*> (o .:? "location") <*>
(o .:? "arguments" .!= mempty)
<*> (o .:? "locals" .!= mempty))
instance ToJSON StackFrame where
toJSON StackFrame'{..}
= object
(catMaybes
[("function" .=) <$> _sfFunction,
("location" .=) <$> _sfLocation,
("arguments" .=) <$> _sfArguments,
("locals" .=) <$> _sfLocals])
data CloudRepoSourceContext = CloudRepoSourceContext'
{ _crscRepoId :: !(Maybe RepoId)
, _crscAliasName :: !(Maybe Text)
, _crscRevisionId :: !(Maybe Text)
, _crscAliasContext :: !(Maybe AliasContext)
} deriving (Eq,Show,Data,Typeable,Generic)
cloudRepoSourceContext
:: CloudRepoSourceContext
cloudRepoSourceContext =
CloudRepoSourceContext'
{ _crscRepoId = Nothing
, _crscAliasName = Nothing
, _crscRevisionId = Nothing
, _crscAliasContext = Nothing
}
crscRepoId :: Lens' CloudRepoSourceContext (Maybe RepoId)
crscRepoId
= lens _crscRepoId (\ s a -> s{_crscRepoId = a})
crscAliasName :: Lens' CloudRepoSourceContext (Maybe Text)
crscAliasName
= lens _crscAliasName
(\ s a -> s{_crscAliasName = a})
crscRevisionId :: Lens' CloudRepoSourceContext (Maybe Text)
crscRevisionId
= lens _crscRevisionId
(\ s a -> s{_crscRevisionId = a})
crscAliasContext :: Lens' CloudRepoSourceContext (Maybe AliasContext)
crscAliasContext
= lens _crscAliasContext
(\ s a -> s{_crscAliasContext = a})
instance FromJSON CloudRepoSourceContext where
parseJSON
= withObject "CloudRepoSourceContext"
(\ o ->
CloudRepoSourceContext' <$>
(o .:? "repoId") <*> (o .:? "aliasName") <*>
(o .:? "revisionId")
<*> (o .:? "aliasContext"))
instance ToJSON CloudRepoSourceContext where
toJSON CloudRepoSourceContext'{..}
= object
(catMaybes
[("repoId" .=) <$> _crscRepoId,
("aliasName" .=) <$> _crscAliasName,
("revisionId" .=) <$> _crscRevisionId,
("aliasContext" .=) <$> _crscAliasContext])
newtype DebuggeeLabels = DebuggeeLabels'
{ _dlAddtional :: HashMap Text Text
} deriving (Eq,Show,Data,Typeable,Generic)
debuggeeLabels
:: HashMap Text Text
-> DebuggeeLabels
debuggeeLabels pDlAddtional_ =
DebuggeeLabels'
{ _dlAddtional = _Coerce # pDlAddtional_
}
dlAddtional :: Lens' DebuggeeLabels (HashMap Text Text)
dlAddtional
= lens _dlAddtional (\ s a -> s{_dlAddtional = a}) .
_Coerce
instance FromJSON DebuggeeLabels where
parseJSON
= withObject "DebuggeeLabels"
(\ o -> DebuggeeLabels' <$> (parseJSONObject o))
instance ToJSON DebuggeeLabels where
toJSON = toJSON . _dlAddtional
data Debuggee = Debuggee'
{ _dStatus :: !(Maybe StatusMessage)
, _dUniquifier :: !(Maybe Text)
, _dProject :: !(Maybe Text)
, _dExtSourceContexts :: !(Maybe [ExtendedSourceContext])
, _dAgentVersion :: !(Maybe Text)
, _dIsDisabled :: !(Maybe Bool)
, _dId :: !(Maybe Text)
, _dLabels :: !(Maybe DebuggeeLabels)
, _dDescription :: !(Maybe Text)
, _dIsInactive :: !(Maybe Bool)
, _dSourceContexts :: !(Maybe [SourceContext])
} deriving (Eq,Show,Data,Typeable,Generic)
debuggee
:: Debuggee
debuggee =
Debuggee'
{ _dStatus = Nothing
, _dUniquifier = Nothing
, _dProject = Nothing
, _dExtSourceContexts = Nothing
, _dAgentVersion = Nothing
, _dIsDisabled = Nothing
, _dId = Nothing
, _dLabels = Nothing
, _dDescription = Nothing
, _dIsInactive = Nothing
, _dSourceContexts = Nothing
}
dStatus :: Lens' Debuggee (Maybe StatusMessage)
dStatus = lens _dStatus (\ s a -> s{_dStatus = a})
dUniquifier :: Lens' Debuggee (Maybe Text)
dUniquifier
= lens _dUniquifier (\ s a -> s{_dUniquifier = a})
dProject :: Lens' Debuggee (Maybe Text)
dProject = lens _dProject (\ s a -> s{_dProject = a})
dExtSourceContexts :: Lens' Debuggee [ExtendedSourceContext]
dExtSourceContexts
= lens _dExtSourceContexts
(\ s a -> s{_dExtSourceContexts = a})
. _Default
. _Coerce
dAgentVersion :: Lens' Debuggee (Maybe Text)
dAgentVersion
= lens _dAgentVersion
(\ s a -> s{_dAgentVersion = a})
dIsDisabled :: Lens' Debuggee (Maybe Bool)
dIsDisabled
= lens _dIsDisabled (\ s a -> s{_dIsDisabled = a})
dId :: Lens' Debuggee (Maybe Text)
dId = lens _dId (\ s a -> s{_dId = a})
dLabels :: Lens' Debuggee (Maybe DebuggeeLabels)
dLabels = lens _dLabels (\ s a -> s{_dLabels = a})
dDescription :: Lens' Debuggee (Maybe Text)
dDescription
= lens _dDescription (\ s a -> s{_dDescription = a})
dIsInactive :: Lens' Debuggee (Maybe Bool)
dIsInactive
= lens _dIsInactive (\ s a -> s{_dIsInactive = a})
dSourceContexts :: Lens' Debuggee [SourceContext]
dSourceContexts
= lens _dSourceContexts
(\ s a -> s{_dSourceContexts = a})
. _Default
. _Coerce
instance FromJSON Debuggee where
parseJSON
= withObject "Debuggee"
(\ o ->
Debuggee' <$>
(o .:? "status") <*> (o .:? "uniquifier") <*>
(o .:? "project")
<*> (o .:? "extSourceContexts" .!= mempty)
<*> (o .:? "agentVersion")
<*> (o .:? "isDisabled")
<*> (o .:? "id")
<*> (o .:? "labels")
<*> (o .:? "description")
<*> (o .:? "isInactive")
<*> (o .:? "sourceContexts" .!= mempty))
instance ToJSON Debuggee where
toJSON Debuggee'{..}
= object
(catMaybes
[("status" .=) <$> _dStatus,
("uniquifier" .=) <$> _dUniquifier,
("project" .=) <$> _dProject,
("extSourceContexts" .=) <$> _dExtSourceContexts,
("agentVersion" .=) <$> _dAgentVersion,
("isDisabled" .=) <$> _dIsDisabled,
("id" .=) <$> _dId, ("labels" .=) <$> _dLabels,
("description" .=) <$> _dDescription,
("isInactive" .=) <$> _dIsInactive,
("sourceContexts" .=) <$> _dSourceContexts])
data CloudWorkspaceSourceContext = CloudWorkspaceSourceContext'
{ _cwscWorkspaceId :: !(Maybe CloudWorkspaceId)
, _cwscSnapshotId :: !(Maybe Text)
} deriving (Eq,Show,Data,Typeable,Generic)
cloudWorkspaceSourceContext
:: CloudWorkspaceSourceContext
cloudWorkspaceSourceContext =
CloudWorkspaceSourceContext'
{ _cwscWorkspaceId = Nothing
, _cwscSnapshotId = Nothing
}
cwscWorkspaceId :: Lens' CloudWorkspaceSourceContext (Maybe CloudWorkspaceId)
cwscWorkspaceId
= lens _cwscWorkspaceId
(\ s a -> s{_cwscWorkspaceId = a})
cwscSnapshotId :: Lens' CloudWorkspaceSourceContext (Maybe Text)
cwscSnapshotId
= lens _cwscSnapshotId
(\ s a -> s{_cwscSnapshotId = a})
instance FromJSON CloudWorkspaceSourceContext where
parseJSON
= withObject "CloudWorkspaceSourceContext"
(\ o ->
CloudWorkspaceSourceContext' <$>
(o .:? "workspaceId") <*> (o .:? "snapshotId"))
instance ToJSON CloudWorkspaceSourceContext where
toJSON CloudWorkspaceSourceContext'{..}
= object
(catMaybes
[("workspaceId" .=) <$> _cwscWorkspaceId,
("snapshotId" .=) <$> _cwscSnapshotId])
newtype RegisterDebuggeeRequest = RegisterDebuggeeRequest'
{ _rDebuggee :: Maybe Debuggee
} deriving (Eq,Show,Data,Typeable,Generic)
registerDebuggeeRequest
:: RegisterDebuggeeRequest
registerDebuggeeRequest =
RegisterDebuggeeRequest'
{ _rDebuggee = Nothing
}
rDebuggee :: Lens' RegisterDebuggeeRequest (Maybe Debuggee)
rDebuggee
= lens _rDebuggee (\ s a -> s{_rDebuggee = a})
instance FromJSON RegisterDebuggeeRequest where
parseJSON
= withObject "RegisterDebuggeeRequest"
(\ o ->
RegisterDebuggeeRequest' <$> (o .:? "debuggee"))
instance ToJSON RegisterDebuggeeRequest where
toJSON RegisterDebuggeeRequest'{..}
= object (catMaybes [("debuggee" .=) <$> _rDebuggee])
data AliasContext = AliasContext'
{ _acKind :: !(Maybe AliasContextKind)
, _acName :: !(Maybe Text)
} deriving (Eq,Show,Data,Typeable,Generic)
aliasContext
:: AliasContext
aliasContext =
AliasContext'
{ _acKind = Nothing
, _acName = Nothing
}
acKind :: Lens' AliasContext (Maybe AliasContextKind)
acKind = lens _acKind (\ s a -> s{_acKind = a})
acName :: Lens' AliasContext (Maybe Text)
acName = lens _acName (\ s a -> s{_acName = a})
instance FromJSON AliasContext where
parseJSON
= withObject "AliasContext"
(\ o ->
AliasContext' <$> (o .:? "kind") <*> (o .:? "name"))
instance ToJSON AliasContext where
toJSON AliasContext'{..}
= object
(catMaybes
[("kind" .=) <$> _acKind, ("name" .=) <$> _acName])
data CloudWorkspaceId = CloudWorkspaceId'
{ _cwiRepoId :: !(Maybe RepoId)
, _cwiName :: !(Maybe Text)
} deriving (Eq,Show,Data,Typeable,Generic)
cloudWorkspaceId
:: CloudWorkspaceId
cloudWorkspaceId =
CloudWorkspaceId'
{ _cwiRepoId = Nothing
, _cwiName = Nothing
}
cwiRepoId :: Lens' CloudWorkspaceId (Maybe RepoId)
cwiRepoId
= lens _cwiRepoId (\ s a -> s{_cwiRepoId = a})
cwiName :: Lens' CloudWorkspaceId (Maybe Text)
cwiName = lens _cwiName (\ s a -> s{_cwiName = a})
instance FromJSON CloudWorkspaceId where
parseJSON
= withObject "CloudWorkspaceId"
(\ o ->
CloudWorkspaceId' <$>
(o .:? "repoId") <*> (o .:? "name"))
instance ToJSON CloudWorkspaceId where
toJSON CloudWorkspaceId'{..}
= object
(catMaybes
[("repoId" .=) <$> _cwiRepoId,
("name" .=) <$> _cwiName])