gogol-binaryauthorization-0.4.0: Google Binary Authorization SDK.

Copyright(c) 2015-2016 Brendan Hay
LicenseMozilla Public License, v. 2.0.
MaintainerBrendan Hay <brendan.g.hay@gmail.com>
Stabilityauto-generated
Portabilitynon-portable (GHC extensions)
Safe HaskellNone
LanguageHaskell2010

Network.Google.BinaryAuthorization.Types

Contents

Description

 
Synopsis

Service Configuration

binaryAuthorizationService :: ServiceConfig Source #

Default request referring to version v1beta1 of the Binary Authorization API. This contains the host and root path used as a starting point for constructing service requests.

OAuth Scopes

cloudPlatformScope :: Proxy '["https://www.googleapis.com/auth/cloud-platform"] Source #

View and manage your data across Google Cloud Platform services

Expr

data Expr Source #

Represents an expression text. Example: title: "User account presence" description: "Determines whether the request has a user account" expression: "size(request.user) > 0"

See: expr smart constructor.

Instances
Eq Expr Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Product

Methods

(==) :: Expr -> Expr -> Bool #

(/=) :: Expr -> Expr -> Bool #

Data Expr Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Expr -> c Expr #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Expr #

toConstr :: Expr -> Constr #

dataTypeOf :: Expr -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Expr) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Expr) #

gmapT :: (forall b. Data b => b -> b) -> Expr -> Expr #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Expr -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Expr -> r #

gmapQ :: (forall d. Data d => d -> u) -> Expr -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Expr -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Expr -> m Expr #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Expr -> m Expr #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Expr -> m Expr #

Show Expr Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Product

Methods

showsPrec :: Int -> Expr -> ShowS #

show :: Expr -> String #

showList :: [Expr] -> ShowS #

Generic Expr Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Product

Associated Types

type Rep Expr :: Type -> Type #

Methods

from :: Expr -> Rep Expr x #

to :: Rep Expr x -> Expr #

ToJSON Expr Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Product

FromJSON Expr Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Product

type Rep Expr Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Product

type Rep Expr = D1 (MetaData "Expr" "Network.Google.BinaryAuthorization.Types.Product" "gogol-binaryauthorization-0.4.0-BhgUYr1FlAtBUJGnGudaWV" False) (C1 (MetaCons "Expr'" PrefixI True) ((S1 (MetaSel (Just "_eLocation") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_eExpression") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) :*: (S1 (MetaSel (Just "_eTitle") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_eDescription") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))

expr :: Expr Source #

Creates a value of Expr with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

eLocation :: Lens' Expr (Maybe Text) Source #

An optional string indicating the location of the expression for error reporting, e.g. a file name and a position in the file.

eExpression :: Lens' Expr (Maybe Text) Source #

Textual representation of an expression in Common Expression Language syntax. The application context of the containing message determines which well-known feature set of CEL is supported.

eTitle :: Lens' Expr (Maybe Text) Source #

An optional title for the expression, i.e. a short string describing its purpose. This can be used e.g. in UIs which allow to enter the expression.

eDescription :: Lens' Expr (Maybe Text) Source #

An optional description of the expression. This is a longer text which describes the expression, e.g. when hovered over it in a UI.

UserOwnedDrydockNote

data UserOwnedDrydockNote Source #

An user owned drydock note references a Drydock ATTESTATION_AUTHORITY Note created by the user.

See: userOwnedDrydockNote smart constructor.

Instances
Eq UserOwnedDrydockNote Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Product

Data UserOwnedDrydockNote Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> UserOwnedDrydockNote -> c UserOwnedDrydockNote #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c UserOwnedDrydockNote #

toConstr :: UserOwnedDrydockNote -> Constr #

dataTypeOf :: UserOwnedDrydockNote -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c UserOwnedDrydockNote) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UserOwnedDrydockNote) #

gmapT :: (forall b. Data b => b -> b) -> UserOwnedDrydockNote -> UserOwnedDrydockNote #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UserOwnedDrydockNote -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UserOwnedDrydockNote -> r #

gmapQ :: (forall d. Data d => d -> u) -> UserOwnedDrydockNote -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> UserOwnedDrydockNote -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> UserOwnedDrydockNote -> m UserOwnedDrydockNote #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> UserOwnedDrydockNote -> m UserOwnedDrydockNote #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> UserOwnedDrydockNote -> m UserOwnedDrydockNote #

Show UserOwnedDrydockNote Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Product

Generic UserOwnedDrydockNote Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Product

Associated Types

type Rep UserOwnedDrydockNote :: Type -> Type #

ToJSON UserOwnedDrydockNote Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Product

FromJSON UserOwnedDrydockNote Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Product

type Rep UserOwnedDrydockNote Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Product

type Rep UserOwnedDrydockNote = D1 (MetaData "UserOwnedDrydockNote" "Network.Google.BinaryAuthorization.Types.Product" "gogol-binaryauthorization-0.4.0-BhgUYr1FlAtBUJGnGudaWV" False) (C1 (MetaCons "UserOwnedDrydockNote'" PrefixI True) (S1 (MetaSel (Just "_uodnDelegationServiceAccountEmail") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: (S1 (MetaSel (Just "_uodnPublicKeys") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [AttestorPublicKey])) :*: S1 (MetaSel (Just "_uodnNoteReference") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))

userOwnedDrydockNote :: UserOwnedDrydockNote Source #

Creates a value of UserOwnedDrydockNote with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

uodnDelegationServiceAccountEmail :: Lens' UserOwnedDrydockNote (Maybe Text) Source #

Output only. This field will contain the service account email address that this Attestor will use as the principal when querying Container Analysis. Attestor administrators must grant this service account the IAM role needed to read attestations from the note_reference in Container Analysis (`containeranalysis.notes.occurrences.viewer`). This email address is fixed for the lifetime of the Attestor, but callers should not make any other assumptions about the service account email; future versions may use an email based on a different naming pattern.

uodnPublicKeys :: Lens' UserOwnedDrydockNote [AttestorPublicKey] Source #

Optional. Public keys that verify attestations signed by this attestor. This field may be updated. If this field is non-empty, one of the specified public keys must verify that an attestation was signed by this attestor for the image specified in the admission request. If this field is empty, this attestor always returns that no valid attestations exist.

uodnNoteReference :: Lens' UserOwnedDrydockNote (Maybe Text) Source #

Required. The Drydock resource name of a ATTESTATION_AUTHORITY Note, created by the user, in the format: `projects/*/notes/*` (or the legacy `providers/*/notes/*`). This field may not be updated. An attestation by this attestor is stored as a Drydock ATTESTATION_AUTHORITY Occurrence that names a container image and that links to this Note. Drydock is an external dependency.

Empty

data Empty Source #

A generic empty message that you can re-use to avoid defining duplicated empty messages in your APIs. A typical example is to use it as the request or the response type of an API method. For instance: service Foo { rpc Bar(google.protobuf.Empty) returns (google.protobuf.Empty); } The JSON representation for `Empty` is empty JSON object `{}`.

See: empty smart constructor.

Instances
Eq Empty Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Product

Methods

(==) :: Empty -> Empty -> Bool #

(/=) :: Empty -> Empty -> Bool #

Data Empty Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Empty -> c Empty #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Empty #

toConstr :: Empty -> Constr #

dataTypeOf :: Empty -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Empty) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Empty) #

gmapT :: (forall b. Data b => b -> b) -> Empty -> Empty #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Empty -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Empty -> r #

gmapQ :: (forall d. Data d => d -> u) -> Empty -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Empty -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Empty -> m Empty #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Empty -> m Empty #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Empty -> m Empty #

Show Empty Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Product

Methods

showsPrec :: Int -> Empty -> ShowS #

show :: Empty -> String #

showList :: [Empty] -> ShowS #

Generic Empty Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Product

Associated Types

type Rep Empty :: Type -> Type #

Methods

from :: Empty -> Rep Empty x #

to :: Rep Empty x -> Empty #

ToJSON Empty Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Product

FromJSON Empty Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Product

type Rep Empty Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Product

type Rep Empty = D1 (MetaData "Empty" "Network.Google.BinaryAuthorization.Types.Product" "gogol-binaryauthorization-0.4.0-BhgUYr1FlAtBUJGnGudaWV" False) (C1 (MetaCons "Empty'" PrefixI False) (U1 :: Type -> Type))

empty :: Empty Source #

Creates a value of Empty with the minimum fields required to make a request.

AdmissionRuleEnforcementMode

data AdmissionRuleEnforcementMode Source #

Required. The action when a pod creation is denied by the admission rule.

Constructors

EnforcementModeUnspecified

ENFORCEMENT_MODE_UNSPECIFIED Mandatory.

EnforcedBlockAndAuditLog

ENFORCED_BLOCK_AND_AUDIT_LOG Enforce the admission rule by blocking the pod creation.

Instances
Enum AdmissionRuleEnforcementMode Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Sum

Eq AdmissionRuleEnforcementMode Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Sum

Data AdmissionRuleEnforcementMode Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Sum

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AdmissionRuleEnforcementMode -> c AdmissionRuleEnforcementMode #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AdmissionRuleEnforcementMode #

toConstr :: AdmissionRuleEnforcementMode -> Constr #

dataTypeOf :: AdmissionRuleEnforcementMode -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c AdmissionRuleEnforcementMode) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AdmissionRuleEnforcementMode) #

gmapT :: (forall b. Data b => b -> b) -> AdmissionRuleEnforcementMode -> AdmissionRuleEnforcementMode #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AdmissionRuleEnforcementMode -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AdmissionRuleEnforcementMode -> r #

gmapQ :: (forall d. Data d => d -> u) -> AdmissionRuleEnforcementMode -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AdmissionRuleEnforcementMode -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AdmissionRuleEnforcementMode -> m AdmissionRuleEnforcementMode #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AdmissionRuleEnforcementMode -> m AdmissionRuleEnforcementMode #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AdmissionRuleEnforcementMode -> m AdmissionRuleEnforcementMode #

Ord AdmissionRuleEnforcementMode Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Sum

Read AdmissionRuleEnforcementMode Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Sum

Show AdmissionRuleEnforcementMode Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Sum

Generic AdmissionRuleEnforcementMode Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Sum

Associated Types

type Rep AdmissionRuleEnforcementMode :: Type -> Type #

Hashable AdmissionRuleEnforcementMode Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Sum

ToJSON AdmissionRuleEnforcementMode Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Sum

FromJSON AdmissionRuleEnforcementMode Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Sum

FromHttpApiData AdmissionRuleEnforcementMode Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Sum

ToHttpApiData AdmissionRuleEnforcementMode Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Sum

type Rep AdmissionRuleEnforcementMode Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Sum

type Rep AdmissionRuleEnforcementMode = D1 (MetaData "AdmissionRuleEnforcementMode" "Network.Google.BinaryAuthorization.Types.Sum" "gogol-binaryauthorization-0.4.0-BhgUYr1FlAtBUJGnGudaWV" False) (C1 (MetaCons "EnforcementModeUnspecified" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "EnforcedBlockAndAuditLog" PrefixI False) (U1 :: Type -> Type))

SetIAMPolicyRequest

data SetIAMPolicyRequest Source #

Request message for `SetIamPolicy` method.

See: setIAMPolicyRequest smart constructor.

Instances
Eq SetIAMPolicyRequest Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Product

Data SetIAMPolicyRequest Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SetIAMPolicyRequest -> c SetIAMPolicyRequest #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SetIAMPolicyRequest #

toConstr :: SetIAMPolicyRequest -> Constr #

dataTypeOf :: SetIAMPolicyRequest -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SetIAMPolicyRequest) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SetIAMPolicyRequest) #

gmapT :: (forall b. Data b => b -> b) -> SetIAMPolicyRequest -> SetIAMPolicyRequest #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SetIAMPolicyRequest -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SetIAMPolicyRequest -> r #

gmapQ :: (forall d. Data d => d -> u) -> SetIAMPolicyRequest -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SetIAMPolicyRequest -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SetIAMPolicyRequest -> m SetIAMPolicyRequest #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SetIAMPolicyRequest -> m SetIAMPolicyRequest #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SetIAMPolicyRequest -> m SetIAMPolicyRequest #

Show SetIAMPolicyRequest Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Product

Generic SetIAMPolicyRequest Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Product

Associated Types

type Rep SetIAMPolicyRequest :: Type -> Type #

ToJSON SetIAMPolicyRequest Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Product

FromJSON SetIAMPolicyRequest Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Product

type Rep SetIAMPolicyRequest Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Product

type Rep SetIAMPolicyRequest = D1 (MetaData "SetIAMPolicyRequest" "Network.Google.BinaryAuthorization.Types.Product" "gogol-binaryauthorization-0.4.0-BhgUYr1FlAtBUJGnGudaWV" True) (C1 (MetaCons "SetIAMPolicyRequest'" PrefixI True) (S1 (MetaSel (Just "_siprPolicy") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe IAMPolicy))))

setIAMPolicyRequest :: SetIAMPolicyRequest Source #

Creates a value of SetIAMPolicyRequest with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

siprPolicy :: Lens' SetIAMPolicyRequest (Maybe IAMPolicy) Source #

REQUIRED: The complete policy to be applied to the `resource`. The size of the policy is limited to a few 10s of KB. An empty policy is a valid policy but certain Cloud Platform services (such as Projects) might reject them.

ListAttestorsResponse

data ListAttestorsResponse Source #

Response message for BinauthzManagementService.ListAttestors.

See: listAttestorsResponse smart constructor.

Instances
Eq ListAttestorsResponse Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Product

Data ListAttestorsResponse Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ListAttestorsResponse -> c ListAttestorsResponse #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ListAttestorsResponse #

toConstr :: ListAttestorsResponse -> Constr #

dataTypeOf :: ListAttestorsResponse -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ListAttestorsResponse) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ListAttestorsResponse) #

gmapT :: (forall b. Data b => b -> b) -> ListAttestorsResponse -> ListAttestorsResponse #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ListAttestorsResponse -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ListAttestorsResponse -> r #

gmapQ :: (forall d. Data d => d -> u) -> ListAttestorsResponse -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ListAttestorsResponse -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ListAttestorsResponse -> m ListAttestorsResponse #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ListAttestorsResponse -> m ListAttestorsResponse #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ListAttestorsResponse -> m ListAttestorsResponse #

Show ListAttestorsResponse Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Product

Generic ListAttestorsResponse Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Product

Associated Types

type Rep ListAttestorsResponse :: Type -> Type #

ToJSON ListAttestorsResponse Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Product

FromJSON ListAttestorsResponse Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Product

type Rep ListAttestorsResponse Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Product

type Rep ListAttestorsResponse = D1 (MetaData "ListAttestorsResponse" "Network.Google.BinaryAuthorization.Types.Product" "gogol-binaryauthorization-0.4.0-BhgUYr1FlAtBUJGnGudaWV" False) (C1 (MetaCons "ListAttestorsResponse'" PrefixI True) (S1 (MetaSel (Just "_larNextPageToken") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_larAttestors") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Attestor]))))

listAttestorsResponse :: ListAttestorsResponse Source #

Creates a value of ListAttestorsResponse with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

larNextPageToken :: Lens' ListAttestorsResponse (Maybe Text) Source #

A token to retrieve the next page of results. Pass this value in the ListAttestorsRequest.page_token field in the subsequent call to the `ListAttestors` method to retrieve the next page of results.

AdmissionWhiteListPattern

data AdmissionWhiteListPattern Source #

An admission whitelist pattern exempts images from checks by admission rules.

See: admissionWhiteListPattern smart constructor.

Instances
Eq AdmissionWhiteListPattern Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Product

Data AdmissionWhiteListPattern Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AdmissionWhiteListPattern -> c AdmissionWhiteListPattern #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AdmissionWhiteListPattern #

toConstr :: AdmissionWhiteListPattern -> Constr #

dataTypeOf :: AdmissionWhiteListPattern -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c AdmissionWhiteListPattern) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AdmissionWhiteListPattern) #

gmapT :: (forall b. Data b => b -> b) -> AdmissionWhiteListPattern -> AdmissionWhiteListPattern #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AdmissionWhiteListPattern -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AdmissionWhiteListPattern -> r #

gmapQ :: (forall d. Data d => d -> u) -> AdmissionWhiteListPattern -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AdmissionWhiteListPattern -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AdmissionWhiteListPattern -> m AdmissionWhiteListPattern #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AdmissionWhiteListPattern -> m AdmissionWhiteListPattern #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AdmissionWhiteListPattern -> m AdmissionWhiteListPattern #

Show AdmissionWhiteListPattern Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Product

Generic AdmissionWhiteListPattern Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Product

Associated Types

type Rep AdmissionWhiteListPattern :: Type -> Type #

ToJSON AdmissionWhiteListPattern Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Product

FromJSON AdmissionWhiteListPattern Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Product

type Rep AdmissionWhiteListPattern Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Product

type Rep AdmissionWhiteListPattern = D1 (MetaData "AdmissionWhiteListPattern" "Network.Google.BinaryAuthorization.Types.Product" "gogol-binaryauthorization-0.4.0-BhgUYr1FlAtBUJGnGudaWV" True) (C1 (MetaCons "AdmissionWhiteListPattern'" PrefixI True) (S1 (MetaSel (Just "_awlpNamePattern") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Text))))

admissionWhiteListPattern :: AdmissionWhiteListPattern Source #

Creates a value of AdmissionWhiteListPattern with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

awlpNamePattern :: Lens' AdmissionWhiteListPattern (Maybe Text) Source #

An image name pattern to whitelist, in the form `registry/path/to/image`. This supports a trailing `*` as a wildcard, but this is allowed only in text after the `registry/` part.

AdmissionRule

data AdmissionRule Source #

An admission rule specifies either that all container images used in a pod creation request must be attested to by one or more attestors, that all pod creations will be allowed, or that all pod creations will be denied. Images matching an admission whitelist pattern are exempted from admission rules and will never block a pod creation.

See: admissionRule smart constructor.

Instances
Eq AdmissionRule Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Product

Data AdmissionRule Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AdmissionRule -> c AdmissionRule #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AdmissionRule #

toConstr :: AdmissionRule -> Constr #

dataTypeOf :: AdmissionRule -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c AdmissionRule) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AdmissionRule) #

gmapT :: (forall b. Data b => b -> b) -> AdmissionRule -> AdmissionRule #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AdmissionRule -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AdmissionRule -> r #

gmapQ :: (forall d. Data d => d -> u) -> AdmissionRule -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AdmissionRule -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AdmissionRule -> m AdmissionRule #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AdmissionRule -> m AdmissionRule #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AdmissionRule -> m AdmissionRule #

Show AdmissionRule Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Product

Generic AdmissionRule Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Product

Associated Types

type Rep AdmissionRule :: Type -> Type #

ToJSON AdmissionRule Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Product

FromJSON AdmissionRule Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Product

type Rep AdmissionRule Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Product

type Rep AdmissionRule = D1 (MetaData "AdmissionRule" "Network.Google.BinaryAuthorization.Types.Product" "gogol-binaryauthorization-0.4.0-BhgUYr1FlAtBUJGnGudaWV" False) (C1 (MetaCons "AdmissionRule'" PrefixI True) (S1 (MetaSel (Just "_arEnforcementMode") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe AdmissionRuleEnforcementMode)) :*: (S1 (MetaSel (Just "_arEvaluationMode") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe AdmissionRuleEvaluationMode)) :*: S1 (MetaSel (Just "_arRequireAttestationsBy") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Text])))))

admissionRule :: AdmissionRule Source #

Creates a value of AdmissionRule with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

arEnforcementMode :: Lens' AdmissionRule (Maybe AdmissionRuleEnforcementMode) Source #

Required. The action when a pod creation is denied by the admission rule.

arEvaluationMode :: Lens' AdmissionRule (Maybe AdmissionRuleEvaluationMode) Source #

Required. How this admission rule will be evaluated.

arRequireAttestationsBy :: Lens' AdmissionRule [Text] Source #

Optional. The resource names of the attestors that must attest to a container image, in the format `projects/*/attestors/*`. Each attestor must exist before a policy can reference it. To add an attestor to a policy the principal issuing the policy change request must be able to read the attestor resource. Note: this field must be non-empty when the evaluation_mode field specifies REQUIRE_ATTESTATION, otherwise it must be empty.

AdmissionRuleEvaluationMode

data AdmissionRuleEvaluationMode Source #

Required. How this admission rule will be evaluated.

Constructors

EvaluationModeUnspecified

EVALUATION_MODE_UNSPECIFIED Mandatory.

AlwaysAllow

ALWAYS_ALLOW This rule allows all all pod creations.

RequireAttestation

REQUIRE_ATTESTATION This rule allows a pod creation if all the attestors listed in 'require_attestations_by' have valid attestations for all of the images in the pod spec.

AlwaysDeny

ALWAYS_DENY This rule denies all pod creations.

Instances
Enum AdmissionRuleEvaluationMode Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Sum

Eq AdmissionRuleEvaluationMode Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Sum

Data AdmissionRuleEvaluationMode Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Sum

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AdmissionRuleEvaluationMode -> c AdmissionRuleEvaluationMode #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AdmissionRuleEvaluationMode #

toConstr :: AdmissionRuleEvaluationMode -> Constr #

dataTypeOf :: AdmissionRuleEvaluationMode -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c AdmissionRuleEvaluationMode) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AdmissionRuleEvaluationMode) #

gmapT :: (forall b. Data b => b -> b) -> AdmissionRuleEvaluationMode -> AdmissionRuleEvaluationMode #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AdmissionRuleEvaluationMode -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AdmissionRuleEvaluationMode -> r #

gmapQ :: (forall d. Data d => d -> u) -> AdmissionRuleEvaluationMode -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AdmissionRuleEvaluationMode -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AdmissionRuleEvaluationMode -> m AdmissionRuleEvaluationMode #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AdmissionRuleEvaluationMode -> m AdmissionRuleEvaluationMode #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AdmissionRuleEvaluationMode -> m AdmissionRuleEvaluationMode #

Ord AdmissionRuleEvaluationMode Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Sum

Read AdmissionRuleEvaluationMode Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Sum

Show AdmissionRuleEvaluationMode Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Sum

Generic AdmissionRuleEvaluationMode Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Sum

Associated Types

type Rep AdmissionRuleEvaluationMode :: Type -> Type #

Hashable AdmissionRuleEvaluationMode Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Sum

ToJSON AdmissionRuleEvaluationMode Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Sum

FromJSON AdmissionRuleEvaluationMode Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Sum

FromHttpApiData AdmissionRuleEvaluationMode Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Sum

ToHttpApiData AdmissionRuleEvaluationMode Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Sum

type Rep AdmissionRuleEvaluationMode Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Sum

type Rep AdmissionRuleEvaluationMode = D1 (MetaData "AdmissionRuleEvaluationMode" "Network.Google.BinaryAuthorization.Types.Sum" "gogol-binaryauthorization-0.4.0-BhgUYr1FlAtBUJGnGudaWV" False) ((C1 (MetaCons "EvaluationModeUnspecified" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "AlwaysAllow" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "RequireAttestation" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "AlwaysDeny" PrefixI False) (U1 :: Type -> Type)))

Xgafv

data Xgafv Source #

V1 error format.

Constructors

X1

1 v1 error format

X2

2 v2 error format

Instances
Enum Xgafv Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Sum

Eq Xgafv Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Sum

Methods

(==) :: Xgafv -> Xgafv -> Bool #

(/=) :: Xgafv -> Xgafv -> Bool #

Data Xgafv Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Sum

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Xgafv -> c Xgafv #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Xgafv #

toConstr :: Xgafv -> Constr #

dataTypeOf :: Xgafv -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Xgafv) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Xgafv) #

gmapT :: (forall b. Data b => b -> b) -> Xgafv -> Xgafv #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Xgafv -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Xgafv -> r #

gmapQ :: (forall d. Data d => d -> u) -> Xgafv -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Xgafv -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Xgafv -> m Xgafv #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Xgafv -> m Xgafv #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Xgafv -> m Xgafv #

Ord Xgafv Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Sum

Methods

compare :: Xgafv -> Xgafv -> Ordering #

(<) :: Xgafv -> Xgafv -> Bool #

(<=) :: Xgafv -> Xgafv -> Bool #

(>) :: Xgafv -> Xgafv -> Bool #

(>=) :: Xgafv -> Xgafv -> Bool #

max :: Xgafv -> Xgafv -> Xgafv #

min :: Xgafv -> Xgafv -> Xgafv #

Read Xgafv Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Sum

Show Xgafv Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Sum

Methods

showsPrec :: Int -> Xgafv -> ShowS #

show :: Xgafv -> String #

showList :: [Xgafv] -> ShowS #

Generic Xgafv Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Sum

Associated Types

type Rep Xgafv :: Type -> Type #

Methods

from :: Xgafv -> Rep Xgafv x #

to :: Rep Xgafv x -> Xgafv #

Hashable Xgafv Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Sum

Methods

hashWithSalt :: Int -> Xgafv -> Int #

hash :: Xgafv -> Int #

ToJSON Xgafv Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Sum

FromJSON Xgafv Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Sum

FromHttpApiData Xgafv Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Sum

ToHttpApiData Xgafv Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Sum

type Rep Xgafv Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Sum

type Rep Xgafv = D1 (MetaData "Xgafv" "Network.Google.BinaryAuthorization.Types.Sum" "gogol-binaryauthorization-0.4.0-BhgUYr1FlAtBUJGnGudaWV" False) (C1 (MetaCons "X1" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "X2" PrefixI False) (U1 :: Type -> Type))

TestIAMPermissionsRequest

data TestIAMPermissionsRequest Source #

Request message for `TestIamPermissions` method.

See: testIAMPermissionsRequest smart constructor.

Instances
Eq TestIAMPermissionsRequest Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Product

Data TestIAMPermissionsRequest Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TestIAMPermissionsRequest -> c TestIAMPermissionsRequest #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TestIAMPermissionsRequest #

toConstr :: TestIAMPermissionsRequest -> Constr #

dataTypeOf :: TestIAMPermissionsRequest -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TestIAMPermissionsRequest) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TestIAMPermissionsRequest) #

gmapT :: (forall b. Data b => b -> b) -> TestIAMPermissionsRequest -> TestIAMPermissionsRequest #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TestIAMPermissionsRequest -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TestIAMPermissionsRequest -> r #

gmapQ :: (forall d. Data d => d -> u) -> TestIAMPermissionsRequest -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TestIAMPermissionsRequest -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TestIAMPermissionsRequest -> m TestIAMPermissionsRequest #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TestIAMPermissionsRequest -> m TestIAMPermissionsRequest #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TestIAMPermissionsRequest -> m TestIAMPermissionsRequest #

Show TestIAMPermissionsRequest Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Product

Generic TestIAMPermissionsRequest Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Product

Associated Types

type Rep TestIAMPermissionsRequest :: Type -> Type #

ToJSON TestIAMPermissionsRequest Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Product

FromJSON TestIAMPermissionsRequest Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Product

type Rep TestIAMPermissionsRequest Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Product

type Rep TestIAMPermissionsRequest = D1 (MetaData "TestIAMPermissionsRequest" "Network.Google.BinaryAuthorization.Types.Product" "gogol-binaryauthorization-0.4.0-BhgUYr1FlAtBUJGnGudaWV" True) (C1 (MetaCons "TestIAMPermissionsRequest'" PrefixI True) (S1 (MetaSel (Just "_tiprPermissions") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe [Text]))))

testIAMPermissionsRequest :: TestIAMPermissionsRequest Source #

Creates a value of TestIAMPermissionsRequest with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

tiprPermissions :: Lens' TestIAMPermissionsRequest [Text] Source #

The set of permissions to check for the `resource`. Permissions with wildcards (such as '*' or 'storage.*') are not allowed. For more information see IAM Overview.

IAMPolicy

data IAMPolicy Source #

Defines an Identity and Access Management (IAM) policy. It is used to specify access control policies for Cloud Platform resources. A `Policy` consists of a list of `bindings`. A `binding` binds a list of `members` to a `role`, where the members can be user accounts, Google groups, Google domains, and service accounts. A `role` is a named list of permissions defined by IAM. **JSON Example** { "bindings": [ { "role": "roles/owner", "members": [ "user:mike'example.com", "group:admins'example.com", "domain:google.com", "serviceAccount:my-other-app'appspot.gserviceaccount.com" ] }, { "role": "roles/viewer", "members": ["user:sean'example.com"] } ] } **YAML Example** bindings: - members: - user:mike'example.com - group:admins'example.com - domain:google.com - serviceAccount:my-other-app'appspot.gserviceaccount.com role: roles/owner - members: - user:sean'example.com role: roles/viewer For a description of IAM and its features, see the IAM developer's guide.

See: iamPolicy smart constructor.

Instances
Eq IAMPolicy Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Product

Data IAMPolicy Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> IAMPolicy -> c IAMPolicy #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c IAMPolicy #

toConstr :: IAMPolicy -> Constr #

dataTypeOf :: IAMPolicy -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c IAMPolicy) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c IAMPolicy) #

gmapT :: (forall b. Data b => b -> b) -> IAMPolicy -> IAMPolicy #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> IAMPolicy -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> IAMPolicy -> r #

gmapQ :: (forall d. Data d => d -> u) -> IAMPolicy -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> IAMPolicy -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> IAMPolicy -> m IAMPolicy #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> IAMPolicy -> m IAMPolicy #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> IAMPolicy -> m IAMPolicy #

Show IAMPolicy Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Product

Generic IAMPolicy Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Product

Associated Types

type Rep IAMPolicy :: Type -> Type #

ToJSON IAMPolicy Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Product

FromJSON IAMPolicy Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Product

type Rep IAMPolicy Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Product

type Rep IAMPolicy = D1 (MetaData "IAMPolicy" "Network.Google.BinaryAuthorization.Types.Product" "gogol-binaryauthorization-0.4.0-BhgUYr1FlAtBUJGnGudaWV" False) (C1 (MetaCons "IAMPolicy'" PrefixI True) (S1 (MetaSel (Just "_ipEtag") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bytes)) :*: (S1 (MetaSel (Just "_ipVersion") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32))) :*: S1 (MetaSel (Just "_ipBindings") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Binding])))))

iamPolicy :: IAMPolicy Source #

Creates a value of IAMPolicy with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

ipEtag :: Lens' IAMPolicy (Maybe ByteString) Source #

`etag` is used for optimistic concurrency control as a way to help prevent simultaneous updates of a policy from overwriting each other. It is strongly suggested that systems make use of the `etag` in the read-modify-write cycle to perform policy updates in order to avoid race conditions: An `etag` is returned in the response to `getIamPolicy`, and systems are expected to put that etag in the request to `setIamPolicy` to ensure that their change will be applied to the same version of the policy. If no `etag` is provided in the call to `setIamPolicy`, then the existing policy is overwritten blindly.

ipBindings :: Lens' IAMPolicy [Binding] Source #

Associates a list of `members` to a `role`. `bindings` with no members will result in an error.

AttestorPublicKey

data AttestorPublicKey Source #

An attestator public key that will be used to verify attestations signed by this attestor.

See: attestorPublicKey smart constructor.

Instances
Eq AttestorPublicKey Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Product

Data AttestorPublicKey Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AttestorPublicKey -> c AttestorPublicKey #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AttestorPublicKey #

toConstr :: AttestorPublicKey -> Constr #

dataTypeOf :: AttestorPublicKey -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c AttestorPublicKey) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AttestorPublicKey) #

gmapT :: (forall b. Data b => b -> b) -> AttestorPublicKey -> AttestorPublicKey #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AttestorPublicKey -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AttestorPublicKey -> r #

gmapQ :: (forall d. Data d => d -> u) -> AttestorPublicKey -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AttestorPublicKey -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AttestorPublicKey -> m AttestorPublicKey #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AttestorPublicKey -> m AttestorPublicKey #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AttestorPublicKey -> m AttestorPublicKey #

Show AttestorPublicKey Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Product

Generic AttestorPublicKey Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Product

Associated Types

type Rep AttestorPublicKey :: Type -> Type #

ToJSON AttestorPublicKey Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Product

FromJSON AttestorPublicKey Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Product

type Rep AttestorPublicKey Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Product

type Rep AttestorPublicKey = D1 (MetaData "AttestorPublicKey" "Network.Google.BinaryAuthorization.Types.Product" "gogol-binaryauthorization-0.4.0-BhgUYr1FlAtBUJGnGudaWV" False) (C1 (MetaCons "AttestorPublicKey'" PrefixI True) (S1 (MetaSel (Just "_apkAsciiArmoredPgpPublicKey") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: (S1 (MetaSel (Just "_apkId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_apkComment") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))

attestorPublicKey :: AttestorPublicKey Source #

Creates a value of AttestorPublicKey with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

apkAsciiArmoredPgpPublicKey :: Lens' AttestorPublicKey (Maybe Text) Source #

ASCII-armored representation of a PGP public key, as the entire output by the command `gpg --export --armor foo'example.com` (either LF or CRLF line endings).

apkId :: Lens' AttestorPublicKey (Maybe Text) Source #

Output only. This field will be overwritten with key ID information, for example, an identifier extracted from a PGP public key. This field may not be updated.

apkComment :: Lens' AttestorPublicKey (Maybe Text) Source #

Optional. A descriptive comment. This field may be updated.

TestIAMPermissionsResponse

data TestIAMPermissionsResponse Source #

Response message for `TestIamPermissions` method.

See: testIAMPermissionsResponse smart constructor.

Instances
Eq TestIAMPermissionsResponse Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Product

Data TestIAMPermissionsResponse Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TestIAMPermissionsResponse -> c TestIAMPermissionsResponse #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TestIAMPermissionsResponse #

toConstr :: TestIAMPermissionsResponse -> Constr #

dataTypeOf :: TestIAMPermissionsResponse -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TestIAMPermissionsResponse) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TestIAMPermissionsResponse) #

gmapT :: (forall b. Data b => b -> b) -> TestIAMPermissionsResponse -> TestIAMPermissionsResponse #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TestIAMPermissionsResponse -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TestIAMPermissionsResponse -> r #

gmapQ :: (forall d. Data d => d -> u) -> TestIAMPermissionsResponse -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TestIAMPermissionsResponse -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TestIAMPermissionsResponse -> m TestIAMPermissionsResponse #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TestIAMPermissionsResponse -> m TestIAMPermissionsResponse #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TestIAMPermissionsResponse -> m TestIAMPermissionsResponse #

Show TestIAMPermissionsResponse Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Product

Generic TestIAMPermissionsResponse Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Product

Associated Types

type Rep TestIAMPermissionsResponse :: Type -> Type #

ToJSON TestIAMPermissionsResponse Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Product

FromJSON TestIAMPermissionsResponse Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Product

type Rep TestIAMPermissionsResponse Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Product

type Rep TestIAMPermissionsResponse = D1 (MetaData "TestIAMPermissionsResponse" "Network.Google.BinaryAuthorization.Types.Product" "gogol-binaryauthorization-0.4.0-BhgUYr1FlAtBUJGnGudaWV" True) (C1 (MetaCons "TestIAMPermissionsResponse'" PrefixI True) (S1 (MetaSel (Just "_tiamprPermissions") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe [Text]))))

testIAMPermissionsResponse :: TestIAMPermissionsResponse Source #

Creates a value of TestIAMPermissionsResponse with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

tiamprPermissions :: Lens' TestIAMPermissionsResponse [Text] Source #

A subset of `TestPermissionsRequest.permissions` that the caller is allowed.

Policy

data Policy Source #

A policy for container image binary authorization.

See: policy smart constructor.

Instances
Eq Policy Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Product

Methods

(==) :: Policy -> Policy -> Bool #

(/=) :: Policy -> Policy -> Bool #

Data Policy Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Policy -> c Policy #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Policy #

toConstr :: Policy -> Constr #

dataTypeOf :: Policy -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Policy) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Policy) #

gmapT :: (forall b. Data b => b -> b) -> Policy -> Policy #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Policy -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Policy -> r #

gmapQ :: (forall d. Data d => d -> u) -> Policy -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Policy -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Policy -> m Policy #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Policy -> m Policy #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Policy -> m Policy #

Show Policy Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Product

Generic Policy Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Product

Associated Types

type Rep Policy :: Type -> Type #

Methods

from :: Policy -> Rep Policy x #

to :: Rep Policy x -> Policy #

ToJSON Policy Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Product

FromJSON Policy Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Product

type Rep Policy Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Product

type Rep Policy = D1 (MetaData "Policy" "Network.Google.BinaryAuthorization.Types.Product" "gogol-binaryauthorization-0.4.0-BhgUYr1FlAtBUJGnGudaWV" False) (C1 (MetaCons "Policy'" PrefixI True) ((S1 (MetaSel (Just "_pDefaultAdmissionRule") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe AdmissionRule)) :*: (S1 (MetaSel (Just "_pAdmissionWhiteListPatterns") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [AdmissionWhiteListPattern])) :*: S1 (MetaSel (Just "_pClusterAdmissionRules") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe PolicyClusterAdmissionRules)))) :*: (S1 (MetaSel (Just "_pUpdateTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DateTime')) :*: (S1 (MetaSel (Just "_pName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_pDescription") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))))

policy :: Policy Source #

Creates a value of Policy with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

pDefaultAdmissionRule :: Lens' Policy (Maybe AdmissionRule) Source #

Required. Default admission rule for a cluster without a per-cluster admission rule.

pAdmissionWhiteListPatterns :: Lens' Policy [AdmissionWhiteListPattern] Source #

Optional. Admission policy whitelisting. A matching admission request will always be permitted. This feature is typically used to exclude Google or third-party infrastructure images from Binary Authorization policies.

pClusterAdmissionRules :: Lens' Policy (Maybe PolicyClusterAdmissionRules) Source #

Optional. Per-cluster admission rules. Cluster spec format: `location.clusterId`. There can be at most one admission rule per cluster spec. A `location` is either a compute zone (e.g. us-central1-a) or a region (e.g. us-central1). For `clusterId` syntax restrictions see https://cloud.google.com/container-engine/reference/rest/v1/projects.zones.clusters.

pUpdateTime :: Lens' Policy (Maybe UTCTime) Source #

Output only. Time when the policy was last updated.

pName :: Lens' Policy (Maybe Text) Source #

Output only. The resource name, in the format `projects/*/policy`. There is at most one policy per project.

pDescription :: Lens' Policy (Maybe Text) Source #

Optional. A descriptive comment.

PolicyClusterAdmissionRules

data PolicyClusterAdmissionRules Source #

Optional. Per-cluster admission rules. Cluster spec format: `location.clusterId`. There can be at most one admission rule per cluster spec. A `location` is either a compute zone (e.g. us-central1-a) or a region (e.g. us-central1). For `clusterId` syntax restrictions see https://cloud.google.com/container-engine/reference/rest/v1/projects.zones.clusters.

See: policyClusterAdmissionRules smart constructor.

Instances
Eq PolicyClusterAdmissionRules Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Product

Data PolicyClusterAdmissionRules Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PolicyClusterAdmissionRules -> c PolicyClusterAdmissionRules #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PolicyClusterAdmissionRules #

toConstr :: PolicyClusterAdmissionRules -> Constr #

dataTypeOf :: PolicyClusterAdmissionRules -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c PolicyClusterAdmissionRules) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PolicyClusterAdmissionRules) #

gmapT :: (forall b. Data b => b -> b) -> PolicyClusterAdmissionRules -> PolicyClusterAdmissionRules #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PolicyClusterAdmissionRules -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PolicyClusterAdmissionRules -> r #

gmapQ :: (forall d. Data d => d -> u) -> PolicyClusterAdmissionRules -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PolicyClusterAdmissionRules -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PolicyClusterAdmissionRules -> m PolicyClusterAdmissionRules #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PolicyClusterAdmissionRules -> m PolicyClusterAdmissionRules #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PolicyClusterAdmissionRules -> m PolicyClusterAdmissionRules #

Show PolicyClusterAdmissionRules Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Product

Generic PolicyClusterAdmissionRules Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Product

Associated Types

type Rep PolicyClusterAdmissionRules :: Type -> Type #

ToJSON PolicyClusterAdmissionRules Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Product

FromJSON PolicyClusterAdmissionRules Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Product

type Rep PolicyClusterAdmissionRules Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Product

type Rep PolicyClusterAdmissionRules = D1 (MetaData "PolicyClusterAdmissionRules" "Network.Google.BinaryAuthorization.Types.Product" "gogol-binaryauthorization-0.4.0-BhgUYr1FlAtBUJGnGudaWV" True) (C1 (MetaCons "PolicyClusterAdmissionRules'" PrefixI True) (S1 (MetaSel (Just "_pcarAddtional") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (HashMap Text AdmissionRule))))

policyClusterAdmissionRules Source #

Creates a value of PolicyClusterAdmissionRules with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

Attestor

data Attestor Source #

An attestor that attests to container image artifacts. An existing attestor cannot be modified except where indicated.

See: attestor smart constructor.

Instances
Eq Attestor Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Product

Data Attestor Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Attestor -> c Attestor #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Attestor #

toConstr :: Attestor -> Constr #

dataTypeOf :: Attestor -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Attestor) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Attestor) #

gmapT :: (forall b. Data b => b -> b) -> Attestor -> Attestor #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Attestor -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Attestor -> r #

gmapQ :: (forall d. Data d => d -> u) -> Attestor -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Attestor -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Attestor -> m Attestor #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Attestor -> m Attestor #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Attestor -> m Attestor #

Show Attestor Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Product

Generic Attestor Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Product

Associated Types

type Rep Attestor :: Type -> Type #

Methods

from :: Attestor -> Rep Attestor x #

to :: Rep Attestor x -> Attestor #

ToJSON Attestor Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Product

FromJSON Attestor Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Product

type Rep Attestor Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Product

type Rep Attestor = D1 (MetaData "Attestor" "Network.Google.BinaryAuthorization.Types.Product" "gogol-binaryauthorization-0.4.0-BhgUYr1FlAtBUJGnGudaWV" False) (C1 (MetaCons "Attestor'" PrefixI True) ((S1 (MetaSel (Just "_aUserOwnedDrydockNote") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe UserOwnedDrydockNote)) :*: S1 (MetaSel (Just "_aUpdateTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DateTime'))) :*: (S1 (MetaSel (Just "_aName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_aDescription") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))

attestor :: Attestor Source #

Creates a value of Attestor with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

aUserOwnedDrydockNote :: Lens' Attestor (Maybe UserOwnedDrydockNote) Source #

A Drydock ATTESTATION_AUTHORITY Note, created by the user.

aUpdateTime :: Lens' Attestor (Maybe UTCTime) Source #

Output only. Time when the attestor was last updated.

aName :: Lens' Attestor (Maybe Text) Source #

Required. The resource name, in the format: `projects/*/attestors/*`. This field may not be updated.

aDescription :: Lens' Attestor (Maybe Text) Source #

Optional. A descriptive comment. This field may be updated. The field may be displayed in chooser dialogs.

Binding

data Binding Source #

Associates `members` with a `role`.

See: binding smart constructor.

Instances
Eq Binding Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Product

Methods

(==) :: Binding -> Binding -> Bool #

(/=) :: Binding -> Binding -> Bool #

Data Binding Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Binding -> c Binding #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Binding #

toConstr :: Binding -> Constr #

dataTypeOf :: Binding -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Binding) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Binding) #

gmapT :: (forall b. Data b => b -> b) -> Binding -> Binding #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Binding -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Binding -> r #

gmapQ :: (forall d. Data d => d -> u) -> Binding -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Binding -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Binding -> m Binding #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Binding -> m Binding #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Binding -> m Binding #

Show Binding Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Product

Generic Binding Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Product

Associated Types

type Rep Binding :: Type -> Type #

Methods

from :: Binding -> Rep Binding x #

to :: Rep Binding x -> Binding #

ToJSON Binding Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Product

FromJSON Binding Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Product

type Rep Binding Source # 
Instance details

Defined in Network.Google.BinaryAuthorization.Types.Product

type Rep Binding = D1 (MetaData "Binding" "Network.Google.BinaryAuthorization.Types.Product" "gogol-binaryauthorization-0.4.0-BhgUYr1FlAtBUJGnGudaWV" False) (C1 (MetaCons "Binding'" PrefixI True) (S1 (MetaSel (Just "_bMembers") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Text])) :*: (S1 (MetaSel (Just "_bRole") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_bCondition") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Expr)))))

binding :: Binding Source #

Creates a value of Binding with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

bMembers :: Lens' Binding [Text] Source #

Specifies the identities requesting access for a Cloud Platform resource. `members` can have the following values: * `allUsers`: A special identifier that represents anyone who is on the internet; with or without a Google account. * `allAuthenticatedUsers`: A special identifier that represents anyone who is authenticated with a Google account or a service account. * `user:{emailid}`: An email address that represents a specific Google account. For example, `alice'gmail.com` . * `serviceAccount:{emailid}`: An email address that represents a service account. For example, `my-other-app'appspot.gserviceaccount.com`. * `group:{emailid}`: An email address that represents a Google group. For example, `admins'example.com`. * `domain:{domain}`: A Google Apps domain name that represents all the users of that domain. For example, `google.com` or `example.com`.

bRole :: Lens' Binding (Maybe Text) Source #

Role that is assigned to `members`. For example, `roles/viewer`, `roles/editor`, or `roles/owner`.

bCondition :: Lens' Binding (Maybe Expr) Source #

Unimplemented. The condition that is associated with this binding. NOTE: an unsatisfied condition will not allow user access via current binding. Different bindings, including their conditions, are examined independently.