{-# 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.SourceRepo.Types.Product where
import Network.Google.Prelude
import Network.Google.SourceRepo.Types.Sum
data AuditConfig = AuditConfig'
{ _acService :: !(Maybe Text)
, _acAuditLogConfigs :: !(Maybe [AuditLogConfig])
} deriving (Eq,Show,Data,Typeable,Generic)
auditConfig
:: AuditConfig
auditConfig =
AuditConfig'
{ _acService = Nothing
, _acAuditLogConfigs = Nothing
}
acService :: Lens' AuditConfig (Maybe Text)
acService
= lens _acService (\ s a -> s{_acService = a})
acAuditLogConfigs :: Lens' AuditConfig [AuditLogConfig]
acAuditLogConfigs
= lens _acAuditLogConfigs
(\ s a -> s{_acAuditLogConfigs = a})
. _Default
. _Coerce
instance FromJSON AuditConfig where
parseJSON
= withObject "AuditConfig"
(\ o ->
AuditConfig' <$>
(o .:? "service") <*>
(o .:? "auditLogConfigs" .!= mempty))
instance ToJSON AuditConfig where
toJSON AuditConfig'{..}
= object
(catMaybes
[("service" .=) <$> _acService,
("auditLogConfigs" .=) <$> _acAuditLogConfigs])
data ProjectConfig = ProjectConfig'
{ _pcPubsubConfigs :: !(Maybe ProjectConfigPubsubConfigs)
, _pcEnablePrivateKeyCheck :: !(Maybe Bool)
, _pcName :: !(Maybe Text)
} deriving (Eq,Show,Data,Typeable,Generic)
projectConfig
:: ProjectConfig
projectConfig =
ProjectConfig'
{ _pcPubsubConfigs = Nothing
, _pcEnablePrivateKeyCheck = Nothing
, _pcName = Nothing
}
pcPubsubConfigs :: Lens' ProjectConfig (Maybe ProjectConfigPubsubConfigs)
pcPubsubConfigs
= lens _pcPubsubConfigs
(\ s a -> s{_pcPubsubConfigs = a})
pcEnablePrivateKeyCheck :: Lens' ProjectConfig (Maybe Bool)
pcEnablePrivateKeyCheck
= lens _pcEnablePrivateKeyCheck
(\ s a -> s{_pcEnablePrivateKeyCheck = a})
pcName :: Lens' ProjectConfig (Maybe Text)
pcName = lens _pcName (\ s a -> s{_pcName = a})
instance FromJSON ProjectConfig where
parseJSON
= withObject "ProjectConfig"
(\ o ->
ProjectConfig' <$>
(o .:? "pubsubConfigs") <*>
(o .:? "enablePrivateKeyCheck")
<*> (o .:? "name"))
instance ToJSON ProjectConfig where
toJSON ProjectConfig'{..}
= object
(catMaybes
[("pubsubConfigs" .=) <$> _pcPubsubConfigs,
("enablePrivateKeyCheck" .=) <$>
_pcEnablePrivateKeyCheck,
("name" .=) <$> _pcName])
data Expr = Expr'
{ _eLocation :: !(Maybe Text)
, _eExpression :: !(Maybe Text)
, _eTitle :: !(Maybe Text)
, _eDescription :: !(Maybe Text)
} deriving (Eq,Show,Data,Typeable,Generic)
expr
:: Expr
expr =
Expr'
{ _eLocation = Nothing
, _eExpression = Nothing
, _eTitle = Nothing
, _eDescription = Nothing
}
eLocation :: Lens' Expr (Maybe Text)
eLocation
= lens _eLocation (\ s a -> s{_eLocation = a})
eExpression :: Lens' Expr (Maybe Text)
eExpression
= lens _eExpression (\ s a -> s{_eExpression = a})
eTitle :: Lens' Expr (Maybe Text)
eTitle = lens _eTitle (\ s a -> s{_eTitle = a})
eDescription :: Lens' Expr (Maybe Text)
eDescription
= lens _eDescription (\ s a -> s{_eDescription = a})
instance FromJSON Expr where
parseJSON
= withObject "Expr"
(\ o ->
Expr' <$>
(o .:? "location") <*> (o .:? "expression") <*>
(o .:? "title")
<*> (o .:? "description"))
instance ToJSON Expr where
toJSON Expr'{..}
= object
(catMaybes
[("location" .=) <$> _eLocation,
("expression" .=) <$> _eExpression,
("title" .=) <$> _eTitle,
("description" .=) <$> _eDescription])
data ListReposResponse = ListReposResponse'
{ _lrrNextPageToken :: !(Maybe Text)
, _lrrRepos :: !(Maybe [Repo])
} deriving (Eq,Show,Data,Typeable,Generic)
listReposResponse
:: ListReposResponse
listReposResponse =
ListReposResponse'
{ _lrrNextPageToken = Nothing
, _lrrRepos = Nothing
}
lrrNextPageToken :: Lens' ListReposResponse (Maybe Text)
lrrNextPageToken
= lens _lrrNextPageToken
(\ s a -> s{_lrrNextPageToken = a})
lrrRepos :: Lens' ListReposResponse [Repo]
lrrRepos
= lens _lrrRepos (\ s a -> s{_lrrRepos = a}) .
_Default
. _Coerce
instance FromJSON ListReposResponse where
parseJSON
= withObject "ListReposResponse"
(\ o ->
ListReposResponse' <$>
(o .:? "nextPageToken") <*>
(o .:? "repos" .!= mempty))
instance ToJSON ListReposResponse where
toJSON ListReposResponse'{..}
= object
(catMaybes
[("nextPageToken" .=) <$> _lrrNextPageToken,
("repos" .=) <$> _lrrRepos])
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 UpdateRepoRequest = UpdateRepoRequest'
{ _urrUpdateMask :: !(Maybe GFieldMask)
, _urrRepo :: !(Maybe Repo)
} deriving (Eq,Show,Data,Typeable,Generic)
updateRepoRequest
:: UpdateRepoRequest
updateRepoRequest =
UpdateRepoRequest'
{ _urrUpdateMask = Nothing
, _urrRepo = Nothing
}
urrUpdateMask :: Lens' UpdateRepoRequest (Maybe GFieldMask)
urrUpdateMask
= lens _urrUpdateMask
(\ s a -> s{_urrUpdateMask = a})
urrRepo :: Lens' UpdateRepoRequest (Maybe Repo)
urrRepo = lens _urrRepo (\ s a -> s{_urrRepo = a})
instance FromJSON UpdateRepoRequest where
parseJSON
= withObject "UpdateRepoRequest"
(\ o ->
UpdateRepoRequest' <$>
(o .:? "updateMask") <*> (o .:? "repo"))
instance ToJSON UpdateRepoRequest where
toJSON UpdateRepoRequest'{..}
= object
(catMaybes
[("updateMask" .=) <$> _urrUpdateMask,
("repo" .=) <$> _urrRepo])
data SetIAMPolicyRequest = SetIAMPolicyRequest'
{ _siprUpdateMask :: !(Maybe GFieldMask)
, _siprPolicy :: !(Maybe Policy)
} deriving (Eq,Show,Data,Typeable,Generic)
setIAMPolicyRequest
:: SetIAMPolicyRequest
setIAMPolicyRequest =
SetIAMPolicyRequest'
{ _siprUpdateMask = Nothing
, _siprPolicy = Nothing
}
siprUpdateMask :: Lens' SetIAMPolicyRequest (Maybe GFieldMask)
siprUpdateMask
= lens _siprUpdateMask
(\ s a -> s{_siprUpdateMask = a})
siprPolicy :: Lens' SetIAMPolicyRequest (Maybe Policy)
siprPolicy
= lens _siprPolicy (\ s a -> s{_siprPolicy = a})
instance FromJSON SetIAMPolicyRequest where
parseJSON
= withObject "SetIAMPolicyRequest"
(\ o ->
SetIAMPolicyRequest' <$>
(o .:? "updateMask") <*> (o .:? "policy"))
instance ToJSON SetIAMPolicyRequest where
toJSON SetIAMPolicyRequest'{..}
= object
(catMaybes
[("updateMask" .=) <$> _siprUpdateMask,
("policy" .=) <$> _siprPolicy])
data PubsubConfig = PubsubConfig'
{ _pcTopic :: !(Maybe Text)
, _pcServiceAccountEmail :: !(Maybe Text)
, _pcMessageFormat :: !(Maybe PubsubConfigMessageFormat)
} deriving (Eq,Show,Data,Typeable,Generic)
pubsubConfig
:: PubsubConfig
pubsubConfig =
PubsubConfig'
{ _pcTopic = Nothing
, _pcServiceAccountEmail = Nothing
, _pcMessageFormat = Nothing
}
pcTopic :: Lens' PubsubConfig (Maybe Text)
pcTopic = lens _pcTopic (\ s a -> s{_pcTopic = a})
pcServiceAccountEmail :: Lens' PubsubConfig (Maybe Text)
pcServiceAccountEmail
= lens _pcServiceAccountEmail
(\ s a -> s{_pcServiceAccountEmail = a})
pcMessageFormat :: Lens' PubsubConfig (Maybe PubsubConfigMessageFormat)
pcMessageFormat
= lens _pcMessageFormat
(\ s a -> s{_pcMessageFormat = a})
instance FromJSON PubsubConfig where
parseJSON
= withObject "PubsubConfig"
(\ o ->
PubsubConfig' <$>
(o .:? "topic") <*> (o .:? "serviceAccountEmail") <*>
(o .:? "messageFormat"))
instance ToJSON PubsubConfig where
toJSON PubsubConfig'{..}
= object
(catMaybes
[("topic" .=) <$> _pcTopic,
("serviceAccountEmail" .=) <$>
_pcServiceAccountEmail,
("messageFormat" .=) <$> _pcMessageFormat])
data UpdateProjectConfigRequest = UpdateProjectConfigRequest'
{ _upcrProjectConfig :: !(Maybe ProjectConfig)
, _upcrUpdateMask :: !(Maybe GFieldMask)
} deriving (Eq,Show,Data,Typeable,Generic)
updateProjectConfigRequest
:: UpdateProjectConfigRequest
updateProjectConfigRequest =
UpdateProjectConfigRequest'
{ _upcrProjectConfig = Nothing
, _upcrUpdateMask = Nothing
}
upcrProjectConfig :: Lens' UpdateProjectConfigRequest (Maybe ProjectConfig)
upcrProjectConfig
= lens _upcrProjectConfig
(\ s a -> s{_upcrProjectConfig = a})
upcrUpdateMask :: Lens' UpdateProjectConfigRequest (Maybe GFieldMask)
upcrUpdateMask
= lens _upcrUpdateMask
(\ s a -> s{_upcrUpdateMask = a})
instance FromJSON UpdateProjectConfigRequest where
parseJSON
= withObject "UpdateProjectConfigRequest"
(\ o ->
UpdateProjectConfigRequest' <$>
(o .:? "projectConfig") <*> (o .:? "updateMask"))
instance ToJSON UpdateProjectConfigRequest where
toJSON UpdateProjectConfigRequest'{..}
= object
(catMaybes
[("projectConfig" .=) <$> _upcrProjectConfig,
("updateMask" .=) <$> _upcrUpdateMask])
newtype TestIAMPermissionsRequest = TestIAMPermissionsRequest'
{ _tiprPermissions :: Maybe [Text]
} deriving (Eq,Show,Data,Typeable,Generic)
testIAMPermissionsRequest
:: TestIAMPermissionsRequest
testIAMPermissionsRequest =
TestIAMPermissionsRequest'
{ _tiprPermissions = Nothing
}
tiprPermissions :: Lens' TestIAMPermissionsRequest [Text]
tiprPermissions
= lens _tiprPermissions
(\ s a -> s{_tiprPermissions = a})
. _Default
. _Coerce
instance FromJSON TestIAMPermissionsRequest where
parseJSON
= withObject "TestIAMPermissionsRequest"
(\ o ->
TestIAMPermissionsRequest' <$>
(o .:? "permissions" .!= mempty))
instance ToJSON TestIAMPermissionsRequest where
toJSON TestIAMPermissionsRequest'{..}
= object
(catMaybes [("permissions" .=) <$> _tiprPermissions])
newtype RepoPubsubConfigs = RepoPubsubConfigs'
{ _rpcAddtional :: HashMap Text PubsubConfig
} deriving (Eq,Show,Data,Typeable,Generic)
repoPubsubConfigs
:: HashMap Text PubsubConfig
-> RepoPubsubConfigs
repoPubsubConfigs pRpcAddtional_ =
RepoPubsubConfigs'
{ _rpcAddtional = _Coerce # pRpcAddtional_
}
rpcAddtional :: Lens' RepoPubsubConfigs (HashMap Text PubsubConfig)
rpcAddtional
= lens _rpcAddtional (\ s a -> s{_rpcAddtional = a})
. _Coerce
instance FromJSON RepoPubsubConfigs where
parseJSON
= withObject "RepoPubsubConfigs"
(\ o -> RepoPubsubConfigs' <$> (parseJSONObject o))
instance ToJSON RepoPubsubConfigs where
toJSON = toJSON . _rpcAddtional
newtype ProjectConfigPubsubConfigs = ProjectConfigPubsubConfigs'
{ _pcpcAddtional :: HashMap Text PubsubConfig
} deriving (Eq,Show,Data,Typeable,Generic)
projectConfigPubsubConfigs
:: HashMap Text PubsubConfig
-> ProjectConfigPubsubConfigs
projectConfigPubsubConfigs pPcpcAddtional_ =
ProjectConfigPubsubConfigs'
{ _pcpcAddtional = _Coerce # pPcpcAddtional_
}
pcpcAddtional :: Lens' ProjectConfigPubsubConfigs (HashMap Text PubsubConfig)
pcpcAddtional
= lens _pcpcAddtional
(\ s a -> s{_pcpcAddtional = a})
. _Coerce
instance FromJSON ProjectConfigPubsubConfigs where
parseJSON
= withObject "ProjectConfigPubsubConfigs"
(\ o ->
ProjectConfigPubsubConfigs' <$> (parseJSONObject o))
instance ToJSON ProjectConfigPubsubConfigs where
toJSON = toJSON . _pcpcAddtional
data Repo = Repo'
{ _rPubsubConfigs :: !(Maybe RepoPubsubConfigs)
, _rSize :: !(Maybe (Textual Int64))
, _rURL :: !(Maybe Text)
, _rName :: !(Maybe Text)
, _rMirrorConfig :: !(Maybe MirrorConfig)
} deriving (Eq,Show,Data,Typeable,Generic)
repo
:: Repo
repo =
Repo'
{ _rPubsubConfigs = Nothing
, _rSize = Nothing
, _rURL = Nothing
, _rName = Nothing
, _rMirrorConfig = Nothing
}
rPubsubConfigs :: Lens' Repo (Maybe RepoPubsubConfigs)
rPubsubConfigs
= lens _rPubsubConfigs
(\ s a -> s{_rPubsubConfigs = a})
rSize :: Lens' Repo (Maybe Int64)
rSize
= lens _rSize (\ s a -> s{_rSize = a}) .
mapping _Coerce
rURL :: Lens' Repo (Maybe Text)
rURL = lens _rURL (\ s a -> s{_rURL = a})
rName :: Lens' Repo (Maybe Text)
rName = lens _rName (\ s a -> s{_rName = a})
rMirrorConfig :: Lens' Repo (Maybe MirrorConfig)
rMirrorConfig
= lens _rMirrorConfig
(\ s a -> s{_rMirrorConfig = a})
instance FromJSON Repo where
parseJSON
= withObject "Repo"
(\ o ->
Repo' <$>
(o .:? "pubsubConfigs") <*> (o .:? "size") <*>
(o .:? "url")
<*> (o .:? "name")
<*> (o .:? "mirrorConfig"))
instance ToJSON Repo where
toJSON Repo'{..}
= object
(catMaybes
[("pubsubConfigs" .=) <$> _rPubsubConfigs,
("size" .=) <$> _rSize, ("url" .=) <$> _rURL,
("name" .=) <$> _rName,
("mirrorConfig" .=) <$> _rMirrorConfig])
newtype TestIAMPermissionsResponse = TestIAMPermissionsResponse'
{ _tiamprPermissions :: Maybe [Text]
} deriving (Eq,Show,Data,Typeable,Generic)
testIAMPermissionsResponse
:: TestIAMPermissionsResponse
testIAMPermissionsResponse =
TestIAMPermissionsResponse'
{ _tiamprPermissions = Nothing
}
tiamprPermissions :: Lens' TestIAMPermissionsResponse [Text]
tiamprPermissions
= lens _tiamprPermissions
(\ s a -> s{_tiamprPermissions = a})
. _Default
. _Coerce
instance FromJSON TestIAMPermissionsResponse where
parseJSON
= withObject "TestIAMPermissionsResponse"
(\ o ->
TestIAMPermissionsResponse' <$>
(o .:? "permissions" .!= mempty))
instance ToJSON TestIAMPermissionsResponse where
toJSON TestIAMPermissionsResponse'{..}
= object
(catMaybes
[("permissions" .=) <$> _tiamprPermissions])
data Policy = Policy'
{ _pAuditConfigs :: !(Maybe [AuditConfig])
, _pEtag :: !(Maybe Bytes)
, _pVersion :: !(Maybe (Textual Int32))
, _pBindings :: !(Maybe [Binding])
} deriving (Eq,Show,Data,Typeable,Generic)
policy
:: Policy
policy =
Policy'
{ _pAuditConfigs = Nothing
, _pEtag = Nothing
, _pVersion = Nothing
, _pBindings = Nothing
}
pAuditConfigs :: Lens' Policy [AuditConfig]
pAuditConfigs
= lens _pAuditConfigs
(\ s a -> s{_pAuditConfigs = a})
. _Default
. _Coerce
pEtag :: Lens' Policy (Maybe ByteString)
pEtag
= lens _pEtag (\ s a -> s{_pEtag = a}) .
mapping _Bytes
pVersion :: Lens' Policy (Maybe Int32)
pVersion
= lens _pVersion (\ s a -> s{_pVersion = a}) .
mapping _Coerce
pBindings :: Lens' Policy [Binding]
pBindings
= lens _pBindings (\ s a -> s{_pBindings = a}) .
_Default
. _Coerce
instance FromJSON Policy where
parseJSON
= withObject "Policy"
(\ o ->
Policy' <$>
(o .:? "auditConfigs" .!= mempty) <*> (o .:? "etag")
<*> (o .:? "version")
<*> (o .:? "bindings" .!= mempty))
instance ToJSON Policy where
toJSON Policy'{..}
= object
(catMaybes
[("auditConfigs" .=) <$> _pAuditConfigs,
("etag" .=) <$> _pEtag, ("version" .=) <$> _pVersion,
("bindings" .=) <$> _pBindings])
data AuditLogConfig = AuditLogConfig'
{ _alcLogType :: !(Maybe AuditLogConfigLogType)
, _alcExemptedMembers :: !(Maybe [Text])
} deriving (Eq,Show,Data,Typeable,Generic)
auditLogConfig
:: AuditLogConfig
auditLogConfig =
AuditLogConfig'
{ _alcLogType = Nothing
, _alcExemptedMembers = Nothing
}
alcLogType :: Lens' AuditLogConfig (Maybe AuditLogConfigLogType)
alcLogType
= lens _alcLogType (\ s a -> s{_alcLogType = a})
alcExemptedMembers :: Lens' AuditLogConfig [Text]
alcExemptedMembers
= lens _alcExemptedMembers
(\ s a -> s{_alcExemptedMembers = a})
. _Default
. _Coerce
instance FromJSON AuditLogConfig where
parseJSON
= withObject "AuditLogConfig"
(\ o ->
AuditLogConfig' <$>
(o .:? "logType") <*>
(o .:? "exemptedMembers" .!= mempty))
instance ToJSON AuditLogConfig where
toJSON AuditLogConfig'{..}
= object
(catMaybes
[("logType" .=) <$> _alcLogType,
("exemptedMembers" .=) <$> _alcExemptedMembers])
data MirrorConfig = MirrorConfig'
{ _mcURL :: !(Maybe Text)
, _mcDeployKeyId :: !(Maybe Text)
, _mcWebhookId :: !(Maybe Text)
} deriving (Eq,Show,Data,Typeable,Generic)
mirrorConfig
:: MirrorConfig
mirrorConfig =
MirrorConfig'
{ _mcURL = Nothing
, _mcDeployKeyId = Nothing
, _mcWebhookId = Nothing
}
mcURL :: Lens' MirrorConfig (Maybe Text)
mcURL = lens _mcURL (\ s a -> s{_mcURL = a})
mcDeployKeyId :: Lens' MirrorConfig (Maybe Text)
mcDeployKeyId
= lens _mcDeployKeyId
(\ s a -> s{_mcDeployKeyId = a})
mcWebhookId :: Lens' MirrorConfig (Maybe Text)
mcWebhookId
= lens _mcWebhookId (\ s a -> s{_mcWebhookId = a})
instance FromJSON MirrorConfig where
parseJSON
= withObject "MirrorConfig"
(\ o ->
MirrorConfig' <$>
(o .:? "url") <*> (o .:? "deployKeyId") <*>
(o .:? "webhookId"))
instance ToJSON MirrorConfig where
toJSON MirrorConfig'{..}
= object
(catMaybes
[("url" .=) <$> _mcURL,
("deployKeyId" .=) <$> _mcDeployKeyId,
("webhookId" .=) <$> _mcWebhookId])
data Binding = Binding'
{ _bMembers :: !(Maybe [Text])
, _bRole :: !(Maybe Text)
, _bCondition :: !(Maybe Expr)
} deriving (Eq,Show,Data,Typeable,Generic)
binding
:: Binding
binding =
Binding'
{ _bMembers = Nothing
, _bRole = Nothing
, _bCondition = Nothing
}
bMembers :: Lens' Binding [Text]
bMembers
= lens _bMembers (\ s a -> s{_bMembers = a}) .
_Default
. _Coerce
bRole :: Lens' Binding (Maybe Text)
bRole = lens _bRole (\ s a -> s{_bRole = a})
bCondition :: Lens' Binding (Maybe Expr)
bCondition
= lens _bCondition (\ s a -> s{_bCondition = a})
instance FromJSON Binding where
parseJSON
= withObject "Binding"
(\ o ->
Binding' <$>
(o .:? "members" .!= mempty) <*> (o .:? "role") <*>
(o .:? "condition"))
instance ToJSON Binding where
toJSON Binding'{..}
= object
(catMaybes
[("members" .=) <$> _bMembers,
("role" .=) <$> _bRole,
("condition" .=) <$> _bCondition])