gogol-cloudasset-0.5.0: Google Cloud Asset 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.CloudAsset.Types

Contents

Description

 
Synopsis

Service Configuration

cloudAssetService :: ServiceConfig Source #

Default request referring to version v1 of the Cloud Asset 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

Status

data Status Source #

The `Status` type defines a logical error model that is suitable for different programming environments, including REST APIs and RPC APIs. It is used by gRPC. The error model is designed to be: - Simple to use and understand for most users - Flexible enough to meet unexpected needs # Overview The `Status` message contains three pieces of data: error code, error message, and error details. The error code should be an enum value of google.rpc.Code, but it may accept additional error codes if needed. The error message should be a developer-facing English message that helps developers *understand* and *resolve* the error. If a localized user-facing error message is needed, put the localized message in the error details or localize it in the client. The optional error details may contain arbitrary information about the error. There is a predefined set of error detail types in the package `google.rpc` that can be used for common error conditions. # Language mapping The `Status` message is the logical representation of the error model, but it is not necessarily the actual wire format. When the `Status` message is exposed in different client libraries and different wire protocols, it can be mapped differently. For example, it will likely be mapped to some exceptions in Java, but more likely mapped to some error codes in C. # Other uses The error model and the `Status` message can be used in a variety of environments, either with or without APIs, to provide a consistent developer experience across different environments. Example uses of this error model include: - Partial errors. If a service needs to return partial errors to the client, it may embed the `Status` in the normal response to indicate the partial errors. - Workflow errors. A typical workflow has multiple steps. Each step may have a `Status` message for error reporting. - Batch operations. If a client uses batch request and batch response, the `Status` message should be used directly inside batch response, one for each error sub-response. - Asynchronous operations. If an API call embeds asynchronous operation results in its response, the status of those operations should be represented directly using the `Status` message. - Logging. If some API errors are stored in logs, the message `Status` could be used directly after any stripping needed for security/privacy reasons.

See: status smart constructor.

Instances
Eq Status Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Product

Methods

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

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

Data Status Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Product

Methods

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

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

toConstr :: Status -> Constr #

dataTypeOf :: Status -> DataType #

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

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

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

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

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

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

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

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

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

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

Show Status Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Product

Generic Status Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Product

Associated Types

type Rep Status :: Type -> Type #

Methods

from :: Status -> Rep Status x #

to :: Rep Status x -> Status #

ToJSON Status Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Product

FromJSON Status Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Product

type Rep Status Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Product

type Rep Status = D1 (MetaData "Status" "Network.Google.CloudAsset.Types.Product" "gogol-cloudasset-0.5.0-EEWTSZpalbM7MHWqhkEXj8" False) (C1 (MetaCons "Status'" PrefixI True) (S1 (MetaSel (Just "_sDetails") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [StatusDetailsItem])) :*: (S1 (MetaSel (Just "_sCode") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32))) :*: S1 (MetaSel (Just "_sMessage") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))

status :: Status Source #

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

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

sDetails :: Lens' Status [StatusDetailsItem] Source #

A list of messages that carry the error details. There is a common set of message types for APIs to use.

sCode :: Lens' Status (Maybe Int32) Source #

The status code, which should be an enum value of google.rpc.Code.

sMessage :: Lens' Status (Maybe Text) Source #

A developer-facing error message, which should be in English. Any user-facing error message should be localized and sent in the google.rpc.Status.details field, or localized by the client.

ExportAssetsRequestContentType

data ExportAssetsRequestContentType Source #

Asset content type. If not specified, no content but the asset name will be returned.

Constructors

EARCTContentTypeUnspecified

CONTENT_TYPE_UNSPECIFIED Unspecified content type.

EARCTResource

RESOURCE Resource metadata.

EARCTIAMPolicy

IAM_POLICY The actual IAM policy set on a resource.

Instances
Enum ExportAssetsRequestContentType Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Sum

Eq ExportAssetsRequestContentType Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Sum

Data ExportAssetsRequestContentType Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Sum

Methods

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

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

toConstr :: ExportAssetsRequestContentType -> Constr #

dataTypeOf :: ExportAssetsRequestContentType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ExportAssetsRequestContentType Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Sum

Read ExportAssetsRequestContentType Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Sum

Show ExportAssetsRequestContentType Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Sum

Generic ExportAssetsRequestContentType Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Sum

Associated Types

type Rep ExportAssetsRequestContentType :: Type -> Type #

Hashable ExportAssetsRequestContentType Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Sum

ToJSON ExportAssetsRequestContentType Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Sum

FromJSON ExportAssetsRequestContentType Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Sum

FromHttpApiData ExportAssetsRequestContentType Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Sum

ToHttpApiData ExportAssetsRequestContentType Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Sum

type Rep ExportAssetsRequestContentType Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Sum

type Rep ExportAssetsRequestContentType = D1 (MetaData "ExportAssetsRequestContentType" "Network.Google.CloudAsset.Types.Sum" "gogol-cloudasset-0.5.0-EEWTSZpalbM7MHWqhkEXj8" False) (C1 (MetaCons "EARCTContentTypeUnspecified" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "EARCTResource" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "EARCTIAMPolicy" PrefixI False) (U1 :: Type -> Type)))

AuditConfig

data AuditConfig Source #

Specifies the audit configuration for a service. The configuration determines which permission types are logged, and what identities, if any, are exempted from logging. An AuditConfig must have one or more AuditLogConfigs. If there are AuditConfigs for both `allServices` and a specific service, the union of the two AuditConfigs is used for that service: the log_types specified in each AuditConfig are enabled, and the exempted_members in each AuditLogConfig are exempted. Example Policy with multiple AuditConfigs: { "audit_configs": [ { "service": "allServices" "audit_log_configs": [ { "log_type": "DATA_READ", "exempted_members": [ "user:foo'gmail.com" ] }, { "log_type": "DATA_WRITE", }, { "log_type": "ADMIN_READ", } ] }, { "service": "fooservice.googleapis.com" "audit_log_configs": [ { "log_type": "DATA_READ", }, { "log_type": "DATA_WRITE", "exempted_members": [ "user:bar'gmail.com" ] } ] } ] } For fooservice, this policy enables DATA_READ, DATA_WRITE and ADMIN_READ logging. It also exempts foo'gmail.com from DATA_READ logging, and bar'gmail.com from DATA_WRITE logging.

See: auditConfig smart constructor.

Instances
Eq AuditConfig Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Product

Data AuditConfig Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Product

Methods

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

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

toConstr :: AuditConfig -> Constr #

dataTypeOf :: AuditConfig -> DataType #

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

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

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

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

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

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

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

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

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

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

Show AuditConfig Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Product

Generic AuditConfig Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Product

Associated Types

type Rep AuditConfig :: Type -> Type #

ToJSON AuditConfig Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Product

FromJSON AuditConfig Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Product

type Rep AuditConfig Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Product

type Rep AuditConfig = D1 (MetaData "AuditConfig" "Network.Google.CloudAsset.Types.Product" "gogol-cloudasset-0.5.0-EEWTSZpalbM7MHWqhkEXj8" False) (C1 (MetaCons "AuditConfig'" PrefixI True) (S1 (MetaSel (Just "_acService") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_acAuditLogConfigs") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [AuditLogConfig]))))

auditConfig :: AuditConfig Source #

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

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

acService :: Lens' AuditConfig (Maybe Text) Source #

Specifies a service that will be enabled for audit logging. For example, `storage.googleapis.com`, `cloudsql.googleapis.com`. `allServices` is a special value that covers all services.

acAuditLogConfigs :: Lens' AuditConfig [AuditLogConfig] Source #

The configuration for logging of each type of permission.

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.CloudAsset.Types.Product

Methods

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

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

Data Expr Source # 
Instance details

Defined in Network.Google.CloudAsset.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.CloudAsset.Types.Product

Methods

showsPrec :: Int -> Expr -> ShowS #

show :: Expr -> String #

showList :: [Expr] -> ShowS #

Generic Expr Source # 
Instance details

Defined in Network.Google.CloudAsset.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.CloudAsset.Types.Product

FromJSON Expr Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Product

type Rep Expr Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Product

type Rep Expr = D1 (MetaData "Expr" "Network.Google.CloudAsset.Types.Product" "gogol-cloudasset-0.5.0-EEWTSZpalbM7MHWqhkEXj8" 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.

Operation

data Operation Source #

This resource represents a long-running operation that is the result of a network API call.

See: operation smart constructor.

Instances
Eq Operation Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Product

Data Operation Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Product

Methods

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

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

toConstr :: Operation -> Constr #

dataTypeOf :: Operation -> DataType #

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

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

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

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

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

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

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

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

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

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

Show Operation Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Product

Generic Operation Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Product

Associated Types

type Rep Operation :: Type -> Type #

ToJSON Operation Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Product

FromJSON Operation Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Product

type Rep Operation Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Product

operation :: Operation Source #

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

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

oDone :: Lens' Operation (Maybe Bool) Source #

If the value is `false`, it means the operation is still in progress. If `true`, the operation is completed, and either `error` or `response` is available.

oError :: Lens' Operation (Maybe Status) Source #

The error result of the operation in case of failure or cancellation.

oResponse :: Lens' Operation (Maybe OperationResponse) Source #

The normal response of the operation in case of success. If the original method returns no data on success, such as `Delete`, the response is `google.protobuf.Empty`. If the original method is standard `Get`/`Create`/`Update`, the response should be the resource. For other methods, the response should have the type `XxxResponse`, where `Xxx` is the original method name. For example, if the original method name is `TakeSnapshot()`, the inferred response type is `TakeSnapshotResponse`.

oName :: Lens' Operation (Maybe Text) Source #

The server-assigned name, which is only unique within the same service that originally returns it. If you use the default HTTP mapping, the `name` should have the format of `operations/some/unique/name`.

oMetadata :: Lens' Operation (Maybe OperationMetadata) Source #

Service-specific metadata associated with the operation. It typically contains progress information and common metadata such as create time. Some services might not provide such metadata. Any method that returns a long-running operation should document the metadata type, if any.

Asset

data Asset Source #

Cloud asset. This includes all Google Cloud Platform resources, Cloud IAM policies, and other non-GCP assets.

See: asset smart constructor.

Instances
Eq Asset Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Product

Methods

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

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

Data Asset Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Product

Methods

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

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

toConstr :: Asset -> Constr #

dataTypeOf :: Asset -> DataType #

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

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

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

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

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

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

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

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

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

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

Show Asset Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Product

Methods

showsPrec :: Int -> Asset -> ShowS #

show :: Asset -> String #

showList :: [Asset] -> ShowS #

Generic Asset Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Product

Associated Types

type Rep Asset :: Type -> Type #

Methods

from :: Asset -> Rep Asset x #

to :: Rep Asset x -> Asset #

ToJSON Asset Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Product

FromJSON Asset Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Product

type Rep Asset Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Product

type Rep Asset = D1 (MetaData "Asset" "Network.Google.CloudAsset.Types.Product" "gogol-cloudasset-0.5.0-EEWTSZpalbM7MHWqhkEXj8" False) (C1 (MetaCons "Asset'" PrefixI True) ((S1 (MetaSel (Just "_aName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_aResource") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Resource))) :*: (S1 (MetaSel (Just "_aIAMPolicy") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Policy)) :*: S1 (MetaSel (Just "_aAssetType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))

asset :: Asset Source #

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

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

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

The full name of the asset. For example: `//compute.googleapis.com/projects/my_project_123/zones/zone1/instances/instance1`. See Resource Names for more information.

aResource :: Lens' Asset (Maybe Resource) Source #

Representation of the resource.

aIAMPolicy :: Lens' Asset (Maybe Policy) Source #

Representation of the actual Cloud IAM policy set on a cloud resource. For each resource, there must be at most one Cloud IAM policy set on it.

aAssetType :: Lens' Asset (Maybe Text) Source #

Type of the asset. Example: "compute.googleapis.com/Disk".

GcsDestination

data GcsDestination Source #

A Cloud Storage location.

See: gcsDestination smart constructor.

Instances
Eq GcsDestination Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Product

Data GcsDestination Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Product

Methods

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

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

toConstr :: GcsDestination -> Constr #

dataTypeOf :: GcsDestination -> DataType #

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

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

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

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

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

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

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

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

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

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

Show GcsDestination Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Product

Generic GcsDestination Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Product

Associated Types

type Rep GcsDestination :: Type -> Type #

ToJSON GcsDestination Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Product

FromJSON GcsDestination Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Product

type Rep GcsDestination Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Product

type Rep GcsDestination = D1 (MetaData "GcsDestination" "Network.Google.CloudAsset.Types.Product" "gogol-cloudasset-0.5.0-EEWTSZpalbM7MHWqhkEXj8" False) (C1 (MetaCons "GcsDestination'" PrefixI True) (S1 (MetaSel (Just "_gdURIPrefix") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_gdURI") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))

gcsDestination :: GcsDestination Source #

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

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

gdURIPrefix :: Lens' GcsDestination (Maybe Text) Source #

The uri prefix of all generated Cloud Storage objects. For example: "gs://bucket_name/object_name_prefix". Each object uri is in format: "gs://bucket_name/object_name_prefix// and only contains assets for that type. starts from 0. For example: "gs://bucket_name/object_name_prefix/compute.googleapis.com/Disk/0" is the first shard of output objects containing all compute.googleapis.com/Disk assets. An INVALID_ARGUMENT error will be returned if file with the same name "gs://bucket_name/object_name_prefix" already exists.

gdURI :: Lens' GcsDestination (Maybe Text) Source #

The uri of the Cloud Storage object. It's the same uri that is used by gsutil. For example: "gs://bucket_name/object_name". See Viewing and Editing Object Metadata for more information.

StatusDetailsItem

data StatusDetailsItem Source #

Instances
Eq StatusDetailsItem Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Product

Data StatusDetailsItem Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Product

Methods

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

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

toConstr :: StatusDetailsItem -> Constr #

dataTypeOf :: StatusDetailsItem -> DataType #

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

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

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

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

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

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

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

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

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

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

Show StatusDetailsItem Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Product

Generic StatusDetailsItem Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Product

Associated Types

type Rep StatusDetailsItem :: Type -> Type #

ToJSON StatusDetailsItem Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Product

FromJSON StatusDetailsItem Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Product

type Rep StatusDetailsItem Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Product

type Rep StatusDetailsItem = D1 (MetaData "StatusDetailsItem" "Network.Google.CloudAsset.Types.Product" "gogol-cloudasset-0.5.0-EEWTSZpalbM7MHWqhkEXj8" True) (C1 (MetaCons "StatusDetailsItem'" PrefixI True) (S1 (MetaSel (Just "_sdiAddtional") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (HashMap Text JSONValue))))

statusDetailsItem Source #

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

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

sdiAddtional :: Lens' StatusDetailsItem (HashMap Text JSONValue) Source #

Properties of the object. Contains field 'type with type URL.

ExportAssetsRequest

data ExportAssetsRequest Source #

Export asset request.

See: exportAssetsRequest smart constructor.

Instances
Eq ExportAssetsRequest Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Product

Data ExportAssetsRequest Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Product

Methods

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

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

toConstr :: ExportAssetsRequest -> Constr #

dataTypeOf :: ExportAssetsRequest -> DataType #

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

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

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

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

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

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

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

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

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

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

Show ExportAssetsRequest Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Product

Generic ExportAssetsRequest Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Product

Associated Types

type Rep ExportAssetsRequest :: Type -> Type #

ToJSON ExportAssetsRequest Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Product

FromJSON ExportAssetsRequest Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Product

type Rep ExportAssetsRequest Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Product

type Rep ExportAssetsRequest = D1 (MetaData "ExportAssetsRequest" "Network.Google.CloudAsset.Types.Product" "gogol-cloudasset-0.5.0-EEWTSZpalbM7MHWqhkEXj8" False) (C1 (MetaCons "ExportAssetsRequest'" PrefixI True) ((S1 (MetaSel (Just "_earReadTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DateTime')) :*: S1 (MetaSel (Just "_earAssetTypes") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Text]))) :*: (S1 (MetaSel (Just "_earOutputConfig") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe OutputConfig)) :*: S1 (MetaSel (Just "_earContentType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ExportAssetsRequestContentType)))))

exportAssetsRequest :: ExportAssetsRequest Source #

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

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

earReadTime :: Lens' ExportAssetsRequest (Maybe UTCTime) Source #

Timestamp to take an asset snapshot. This can only be set to a timestamp between 2018-10-02 UTC (inclusive) and the current time. If not specified, the current time will be used. Due to delays in resource data collection and indexing, there is a volatile window during which running the same query may get different results.

earAssetTypes :: Lens' ExportAssetsRequest [Text] Source #

A list of asset types of which to take a snapshot for. For example: "compute.googleapis.com/Disk". If specified, only matching assets will be returned. See Introduction to Cloud Asset Inventory for all supported asset types.

earOutputConfig :: Lens' ExportAssetsRequest (Maybe OutputConfig) Source #

Required. Output configuration indicating where the results will be output to. All results will be in newline delimited JSON format.

earContentType :: Lens' ExportAssetsRequest (Maybe ExportAssetsRequestContentType) Source #

Asset content type. If not specified, no content but the asset name will be returned.

TimeWindow

data TimeWindow Source #

A time window of (start_time, end_time].

See: timeWindow smart constructor.

Instances
Eq TimeWindow Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Product

Data TimeWindow Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Product

Methods

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

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

toConstr :: TimeWindow -> Constr #

dataTypeOf :: TimeWindow -> DataType #

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

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

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

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

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

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

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

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

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

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

Show TimeWindow Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Product

Generic TimeWindow Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Product

Associated Types

type Rep TimeWindow :: Type -> Type #

ToJSON TimeWindow Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Product

FromJSON TimeWindow Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Product

type Rep TimeWindow Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Product

type Rep TimeWindow = D1 (MetaData "TimeWindow" "Network.Google.CloudAsset.Types.Product" "gogol-cloudasset-0.5.0-EEWTSZpalbM7MHWqhkEXj8" False) (C1 (MetaCons "TimeWindow'" PrefixI True) (S1 (MetaSel (Just "_twStartTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DateTime')) :*: S1 (MetaSel (Just "_twEndTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DateTime'))))

timeWindow :: TimeWindow Source #

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

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

twStartTime :: Lens' TimeWindow (Maybe UTCTime) Source #

Start time of the time window (exclusive).

twEndTime :: Lens' TimeWindow (Maybe UTCTime) Source #

End time of the time window (inclusive). Current timestamp if not specified.

TemporalAsset

data TemporalAsset Source #

Temporal asset. In addition to the asset, the temporal asset includes the status of the asset and valid from and to time of it.

See: temporalAsset smart constructor.

Instances
Eq TemporalAsset Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Product

Data TemporalAsset Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Product

Methods

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

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

toConstr :: TemporalAsset -> Constr #

dataTypeOf :: TemporalAsset -> DataType #

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

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

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

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

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

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

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

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

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

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

Show TemporalAsset Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Product

Generic TemporalAsset Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Product

Associated Types

type Rep TemporalAsset :: Type -> Type #

ToJSON TemporalAsset Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Product

FromJSON TemporalAsset Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Product

type Rep TemporalAsset Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Product

type Rep TemporalAsset = D1 (MetaData "TemporalAsset" "Network.Google.CloudAsset.Types.Product" "gogol-cloudasset-0.5.0-EEWTSZpalbM7MHWqhkEXj8" False) (C1 (MetaCons "TemporalAsset'" PrefixI True) (S1 (MetaSel (Just "_taWindow") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe TimeWindow)) :*: (S1 (MetaSel (Just "_taAsset") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Asset)) :*: S1 (MetaSel (Just "_taDeleted") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool)))))

temporalAsset :: TemporalAsset Source #

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

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

taWindow :: Lens' TemporalAsset (Maybe TimeWindow) Source #

The time window when the asset data and state was observed.

taDeleted :: Lens' TemporalAsset (Maybe Bool) Source #

If the asset is deleted or not.

AuditLogConfigLogType

data AuditLogConfigLogType Source #

The log type that this config enables.

Constructors

LogTypeUnspecified

LOG_TYPE_UNSPECIFIED Default case. Should never be this.

AdminRead

ADMIN_READ Admin reads. Example: CloudIAM getIamPolicy

DataWrite

DATA_WRITE Data writes. Example: CloudSQL Users create

DataRead

DATA_READ Data reads. Example: CloudSQL Users list

Instances
Enum AuditLogConfigLogType Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Sum

Eq AuditLogConfigLogType Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Sum

Data AuditLogConfigLogType Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Sum

Methods

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

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

toConstr :: AuditLogConfigLogType -> Constr #

dataTypeOf :: AuditLogConfigLogType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord AuditLogConfigLogType Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Sum

Read AuditLogConfigLogType Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Sum

Show AuditLogConfigLogType Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Sum

Generic AuditLogConfigLogType Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Sum

Associated Types

type Rep AuditLogConfigLogType :: Type -> Type #

Hashable AuditLogConfigLogType Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Sum

ToJSON AuditLogConfigLogType Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Sum

FromJSON AuditLogConfigLogType Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Sum

FromHttpApiData AuditLogConfigLogType Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Sum

ToHttpApiData AuditLogConfigLogType Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Sum

type Rep AuditLogConfigLogType Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Sum

type Rep AuditLogConfigLogType = D1 (MetaData "AuditLogConfigLogType" "Network.Google.CloudAsset.Types.Sum" "gogol-cloudasset-0.5.0-EEWTSZpalbM7MHWqhkEXj8" False) ((C1 (MetaCons "LogTypeUnspecified" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "AdminRead" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "DataWrite" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "DataRead" PrefixI False) (U1 :: Type -> Type)))

Resource

data Resource Source #

Representation of a cloud resource.

See: resource smart constructor.

Instances
Eq Resource Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Product

Data Resource Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Product

Methods

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

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

toConstr :: Resource -> Constr #

dataTypeOf :: Resource -> DataType #

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

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

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

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

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

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

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

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

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

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

Show Resource Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Product

Generic Resource Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Product

Associated Types

type Rep Resource :: Type -> Type #

Methods

from :: Resource -> Rep Resource x #

to :: Rep Resource x -> Resource #

ToJSON Resource Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Product

FromJSON Resource Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Product

type Rep Resource Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Product

type Rep Resource = D1 (MetaData "Resource" "Network.Google.CloudAsset.Types.Product" "gogol-cloudasset-0.5.0-EEWTSZpalbM7MHWqhkEXj8" False) (C1 (MetaCons "Resource'" PrefixI True) ((S1 (MetaSel (Just "_rParent") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: (S1 (MetaSel (Just "_rData") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ResourceData)) :*: S1 (MetaSel (Just "_rVersion") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) :*: (S1 (MetaSel (Just "_rDiscoveryName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: (S1 (MetaSel (Just "_rDiscoveryDocumentURI") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_rResourceURL") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))))

resource :: Resource Source #

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

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

rParent :: Lens' Resource (Maybe Text) Source #

The full name of the immediate parent of this resource. See Resource Names for more information. For GCP assets, it is the parent resource defined in the Cloud IAM policy hierarchy. For example: `"//cloudresourcemanager.googleapis.com/projects/my_project_123"`. For third-party assets, it is up to the users to define.

rData :: Lens' Resource (Maybe ResourceData) Source #

The content of the resource, in which some sensitive fields are scrubbed away and may not be present.

rVersion :: Lens' Resource (Maybe Text) Source #

The API version. Example: "v1".

rDiscoveryName :: Lens' Resource (Maybe Text) Source #

The JSON schema name listed in the discovery document. Example: "Project". It will be left unspecified for resources (such as Cloud Bigtable) without a discovery-based API.

rDiscoveryDocumentURI :: Lens' Resource (Maybe Text) Source #

The URL of the discovery document containing the resource's JSON schema. For example: `"https://www.googleapis.com/discovery/v1/apis/compute/v1/rest"`. It will be left unspecified for resources without a discovery-based API, such as Cloud Bigtable.

rResourceURL :: Lens' Resource (Maybe Text) Source #

The REST URL for accessing the resource. An HTTP GET operation using this URL returns the resource itself. Example: `https://cloudresourcemanager.googleapis.com/v1/projects/my-project-123`. It will be left unspecified for resources without a REST API.

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.CloudAsset.Types.Sum

Eq Xgafv Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Sum

Methods

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

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

Data Xgafv Source # 
Instance details

Defined in Network.Google.CloudAsset.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.CloudAsset.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.CloudAsset.Types.Sum

Show Xgafv Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Sum

Methods

showsPrec :: Int -> Xgafv -> ShowS #

show :: Xgafv -> String #

showList :: [Xgafv] -> ShowS #

Generic Xgafv Source # 
Instance details

Defined in Network.Google.CloudAsset.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.CloudAsset.Types.Sum

Methods

hashWithSalt :: Int -> Xgafv -> Int #

hash :: Xgafv -> Int #

ToJSON Xgafv Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Sum

FromJSON Xgafv Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Sum

FromHttpApiData Xgafv Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Sum

ToHttpApiData Xgafv Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Sum

type Rep Xgafv Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Sum

type Rep Xgafv = D1 (MetaData "Xgafv" "Network.Google.CloudAsset.Types.Sum" "gogol-cloudasset-0.5.0-EEWTSZpalbM7MHWqhkEXj8" False) (C1 (MetaCons "X1" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "X2" PrefixI False) (U1 :: Type -> Type))

ResourceData

data ResourceData Source #

The content of the resource, in which some sensitive fields are scrubbed away and may not be present.

See: resourceData smart constructor.

Instances
Eq ResourceData Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Product

Data ResourceData Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Product

Methods

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

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

toConstr :: ResourceData -> Constr #

dataTypeOf :: ResourceData -> DataType #

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

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

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

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

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

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

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

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

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

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

Show ResourceData Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Product

Generic ResourceData Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Product

Associated Types

type Rep ResourceData :: Type -> Type #

ToJSON ResourceData Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Product

FromJSON ResourceData Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Product

type Rep ResourceData Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Product

type Rep ResourceData = D1 (MetaData "ResourceData" "Network.Google.CloudAsset.Types.Product" "gogol-cloudasset-0.5.0-EEWTSZpalbM7MHWqhkEXj8" True) (C1 (MetaCons "ResourceData'" PrefixI True) (S1 (MetaSel (Just "_rdAddtional") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (HashMap Text JSONValue))))

resourceData Source #

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

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

rdAddtional :: Lens' ResourceData (HashMap Text JSONValue) Source #

Properties of the object.

OutputConfig

data OutputConfig Source #

Output configuration for export assets destination.

See: outputConfig smart constructor.

Instances
Eq OutputConfig Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Product

Data OutputConfig Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Product

Methods

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

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

toConstr :: OutputConfig -> Constr #

dataTypeOf :: OutputConfig -> DataType #

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

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

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

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

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

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

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

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

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

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

Show OutputConfig Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Product

Generic OutputConfig Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Product

Associated Types

type Rep OutputConfig :: Type -> Type #

ToJSON OutputConfig Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Product

FromJSON OutputConfig Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Product

type Rep OutputConfig Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Product

type Rep OutputConfig = D1 (MetaData "OutputConfig" "Network.Google.CloudAsset.Types.Product" "gogol-cloudasset-0.5.0-EEWTSZpalbM7MHWqhkEXj8" True) (C1 (MetaCons "OutputConfig'" PrefixI True) (S1 (MetaSel (Just "_ocGcsDestination") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe GcsDestination))))

outputConfig :: OutputConfig Source #

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

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

ocGcsDestination :: Lens' OutputConfig (Maybe GcsDestination) Source #

Destination on Cloud Storage.

Policy

data Policy 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: policy smart constructor.

Instances
Eq Policy Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Product

Methods

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

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

Data Policy Source # 
Instance details

Defined in Network.Google.CloudAsset.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.CloudAsset.Types.Product

Generic Policy Source # 
Instance details

Defined in Network.Google.CloudAsset.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.CloudAsset.Types.Product

FromJSON Policy Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Product

type Rep Policy Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Product

type Rep Policy = D1 (MetaData "Policy" "Network.Google.CloudAsset.Types.Product" "gogol-cloudasset-0.5.0-EEWTSZpalbM7MHWqhkEXj8" False) (C1 (MetaCons "Policy'" PrefixI True) ((S1 (MetaSel (Just "_pAuditConfigs") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [AuditConfig])) :*: S1 (MetaSel (Just "_pEtag") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bytes))) :*: (S1 (MetaSel (Just "_pVersion") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32))) :*: S1 (MetaSel (Just "_pBindings") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Binding])))))

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:

pAuditConfigs :: Lens' Policy [AuditConfig] Source #

Specifies cloud audit logging configuration for this policy.

pEtag :: Lens' Policy (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.

pBindings :: Lens' Policy [Binding] Source #

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

BatchGetAssetsHistoryResponse

data BatchGetAssetsHistoryResponse Source #

Batch get assets history response.

See: batchGetAssetsHistoryResponse smart constructor.

Instances
Eq BatchGetAssetsHistoryResponse Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Product

Data BatchGetAssetsHistoryResponse Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Product

Methods

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

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

toConstr :: BatchGetAssetsHistoryResponse -> Constr #

dataTypeOf :: BatchGetAssetsHistoryResponse -> DataType #

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

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

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

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

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

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

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

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

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

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

Show BatchGetAssetsHistoryResponse Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Product

Generic BatchGetAssetsHistoryResponse Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Product

Associated Types

type Rep BatchGetAssetsHistoryResponse :: Type -> Type #

ToJSON BatchGetAssetsHistoryResponse Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Product

FromJSON BatchGetAssetsHistoryResponse Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Product

type Rep BatchGetAssetsHistoryResponse Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Product

type Rep BatchGetAssetsHistoryResponse = D1 (MetaData "BatchGetAssetsHistoryResponse" "Network.Google.CloudAsset.Types.Product" "gogol-cloudasset-0.5.0-EEWTSZpalbM7MHWqhkEXj8" True) (C1 (MetaCons "BatchGetAssetsHistoryResponse'" PrefixI True) (S1 (MetaSel (Just "_bgahrAssets") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe [TemporalAsset]))))

batchGetAssetsHistoryResponse :: BatchGetAssetsHistoryResponse Source #

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

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

bgahrAssets :: Lens' BatchGetAssetsHistoryResponse [TemporalAsset] Source #

A list of assets with valid time windows.

OperationMetadata

data OperationMetadata Source #

Service-specific metadata associated with the operation. It typically contains progress information and common metadata such as create time. Some services might not provide such metadata. Any method that returns a long-running operation should document the metadata type, if any.

See: operationMetadata smart constructor.

Instances
Eq OperationMetadata Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Product

Data OperationMetadata Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Product

Methods

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

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

toConstr :: OperationMetadata -> Constr #

dataTypeOf :: OperationMetadata -> DataType #

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

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

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

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

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

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

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

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

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

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

Show OperationMetadata Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Product

Generic OperationMetadata Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Product

Associated Types

type Rep OperationMetadata :: Type -> Type #

ToJSON OperationMetadata Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Product

FromJSON OperationMetadata Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Product

type Rep OperationMetadata Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Product

type Rep OperationMetadata = D1 (MetaData "OperationMetadata" "Network.Google.CloudAsset.Types.Product" "gogol-cloudasset-0.5.0-EEWTSZpalbM7MHWqhkEXj8" True) (C1 (MetaCons "OperationMetadata'" PrefixI True) (S1 (MetaSel (Just "_omAddtional") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (HashMap Text JSONValue))))

operationMetadata Source #

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

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

omAddtional :: Lens' OperationMetadata (HashMap Text JSONValue) Source #

Properties of the object. Contains field 'type with type URL.

AuditLogConfig

data AuditLogConfig Source #

Provides the configuration for logging a type of permissions. Example: { "audit_log_configs": [ { "log_type": "DATA_READ", "exempted_members": [ "user:foo'gmail.com" ] }, { "log_type": "DATA_WRITE", } ] } This enables 'DATA_READ' and 'DATA_WRITE' logging, while exempting foo'gmail.com from DATA_READ logging.

See: auditLogConfig smart constructor.

Instances
Eq AuditLogConfig Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Product

Data AuditLogConfig Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Product

Methods

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

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

toConstr :: AuditLogConfig -> Constr #

dataTypeOf :: AuditLogConfig -> DataType #

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

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

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

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

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

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

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

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

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

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

Show AuditLogConfig Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Product

Generic AuditLogConfig Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Product

Associated Types

type Rep AuditLogConfig :: Type -> Type #

ToJSON AuditLogConfig Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Product

FromJSON AuditLogConfig Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Product

type Rep AuditLogConfig Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Product

type Rep AuditLogConfig = D1 (MetaData "AuditLogConfig" "Network.Google.CloudAsset.Types.Product" "gogol-cloudasset-0.5.0-EEWTSZpalbM7MHWqhkEXj8" False) (C1 (MetaCons "AuditLogConfig'" PrefixI True) (S1 (MetaSel (Just "_alcLogType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe AuditLogConfigLogType)) :*: S1 (MetaSel (Just "_alcExemptedMembers") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Text]))))

auditLogConfig :: AuditLogConfig Source #

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

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

alcLogType :: Lens' AuditLogConfig (Maybe AuditLogConfigLogType) Source #

The log type that this config enables.

alcExemptedMembers :: Lens' AuditLogConfig [Text] Source #

Specifies the identities that do not cause logging for this type of permission. Follows the same format of Binding.members.

OperationResponse

data OperationResponse Source #

The normal response of the operation in case of success. If the original method returns no data on success, such as `Delete`, the response is `google.protobuf.Empty`. If the original method is standard `Get`/`Create`/`Update`, the response should be the resource. For other methods, the response should have the type `XxxResponse`, where `Xxx` is the original method name. For example, if the original method name is `TakeSnapshot()`, the inferred response type is `TakeSnapshotResponse`.

See: operationResponse smart constructor.

Instances
Eq OperationResponse Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Product

Data OperationResponse Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Product

Methods

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

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

toConstr :: OperationResponse -> Constr #

dataTypeOf :: OperationResponse -> DataType #

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

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

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

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

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

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

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

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

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

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

Show OperationResponse Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Product

Generic OperationResponse Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Product

Associated Types

type Rep OperationResponse :: Type -> Type #

ToJSON OperationResponse Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Product

FromJSON OperationResponse Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Product

type Rep OperationResponse Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Product

type Rep OperationResponse = D1 (MetaData "OperationResponse" "Network.Google.CloudAsset.Types.Product" "gogol-cloudasset-0.5.0-EEWTSZpalbM7MHWqhkEXj8" True) (C1 (MetaCons "OperationResponse'" PrefixI True) (S1 (MetaSel (Just "_orAddtional") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (HashMap Text JSONValue))))

operationResponse Source #

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

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

orAddtional :: Lens' OperationResponse (HashMap Text JSONValue) Source #

Properties of the object. Contains field 'type with type URL.

Binding

data Binding Source #

Associates `members` with a `role`.

See: binding smart constructor.

Instances
Eq Binding Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Product

Methods

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

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

Data Binding Source # 
Instance details

Defined in Network.Google.CloudAsset.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.CloudAsset.Types.Product

Generic Binding Source # 
Instance details

Defined in Network.Google.CloudAsset.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.CloudAsset.Types.Product

FromJSON Binding Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Product

type Rep Binding Source # 
Instance details

Defined in Network.Google.CloudAsset.Types.Product

type Rep Binding = D1 (MetaData "Binding" "Network.Google.CloudAsset.Types.Product" "gogol-cloudasset-0.5.0-EEWTSZpalbM7MHWqhkEXj8" 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}`: The G Suite domain (primary) 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 #

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.