gogol-storage-0.3.0: Google Cloud Storage JSON 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.Storage.Types

Contents

Description

 

Synopsis

Service Configuration

storageService :: ServiceConfig Source #

Default request referring to version v1 of the Cloud Storage JSON API. This contains the host and root path used as a starting point for constructing service requests.

OAuth Scopes

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

View your data across Google Cloud Platform services

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

View and manage your data across Google Cloud Platform services

storageReadOnlyScope :: Proxy '["https://www.googleapis.com/auth/devstorage.read_only"] Source #

View your data in Google Cloud Storage

storageReadWriteScope :: Proxy '["https://www.googleapis.com/auth/devstorage.read_write"] Source #

Manage your data in Google Cloud Storage

storageFullControlScope :: Proxy '["https://www.googleapis.com/auth/devstorage.full_control"] Source #

Manage your data and permissions in Google Cloud Storage

ObjectOwner

data ObjectOwner Source #

The owner of the object. This will always be the uploader of the object.

See: objectOwner smart constructor.

Instances

Eq ObjectOwner Source # 
Data ObjectOwner Source # 

Methods

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

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

toConstr :: ObjectOwner -> Constr #

dataTypeOf :: ObjectOwner -> DataType #

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

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

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

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

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

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

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

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

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

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

Show ObjectOwner Source # 
Generic ObjectOwner Source # 

Associated Types

type Rep ObjectOwner :: * -> * #

ToJSON ObjectOwner Source # 
FromJSON ObjectOwner Source # 
type Rep ObjectOwner Source # 
type Rep ObjectOwner = D1 (MetaData "ObjectOwner" "Network.Google.Storage.Types.Product" "gogol-storage-0.3.0-DGwRnfj7WmaH5CaBqC8AR9" False) (C1 (MetaCons "ObjectOwner'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_ooEntity") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_ooEntityId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))

objectOwner :: ObjectOwner Source #

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

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

ooEntity :: Lens' ObjectOwner (Maybe Text) Source #

The entity, in the form user-userId.

ooEntityId :: Lens' ObjectOwner (Maybe Text) Source #

The ID for the entity.

ObjectsInsertProjection

data ObjectsInsertProjection Source #

Set of properties to return. Defaults to noAcl, unless the object resource specifies the acl property, when it defaults to full.

Constructors

Full

full Include all properties.

NoACL

noAcl Omit the owner, acl property.

Instances

Enum ObjectsInsertProjection Source # 
Eq ObjectsInsertProjection Source # 
Data ObjectsInsertProjection Source # 

Methods

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

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

toConstr :: ObjectsInsertProjection -> Constr #

dataTypeOf :: ObjectsInsertProjection -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ObjectsInsertProjection Source # 
Read ObjectsInsertProjection Source # 
Show ObjectsInsertProjection Source # 
Generic ObjectsInsertProjection Source # 
Hashable ObjectsInsertProjection Source # 
ToJSON ObjectsInsertProjection Source # 
FromJSON ObjectsInsertProjection Source # 
FromHttpApiData ObjectsInsertProjection Source # 
ToHttpApiData ObjectsInsertProjection Source # 
type Rep ObjectsInsertProjection Source # 
type Rep ObjectsInsertProjection = D1 (MetaData "ObjectsInsertProjection" "Network.Google.Storage.Types.Sum" "gogol-storage-0.3.0-DGwRnfj7WmaH5CaBqC8AR9" False) ((:+:) (C1 (MetaCons "Full" PrefixI False) U1) (C1 (MetaCons "NoACL" PrefixI False) U1))

BucketVersioning

data BucketVersioning Source #

The bucket's versioning configuration.

See: bucketVersioning smart constructor.

Instances

Eq BucketVersioning Source # 
Data BucketVersioning Source # 

Methods

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

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

toConstr :: BucketVersioning -> Constr #

dataTypeOf :: BucketVersioning -> DataType #

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

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

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

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

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

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

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

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

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

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

Show BucketVersioning Source # 
Generic BucketVersioning Source # 
ToJSON BucketVersioning Source # 
FromJSON BucketVersioning Source # 
type Rep BucketVersioning Source # 
type Rep BucketVersioning = D1 (MetaData "BucketVersioning" "Network.Google.Storage.Types.Product" "gogol-storage-0.3.0-DGwRnfj7WmaH5CaBqC8AR9" True) (C1 (MetaCons "BucketVersioning'" PrefixI True) (S1 (MetaSel (Just Symbol "_bvEnabled") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Bool))))

bucketVersioning :: BucketVersioning Source #

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

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

bvEnabled :: Lens' BucketVersioning (Maybe Bool) Source #

While set to true, versioning is fully enabled for this bucket.

BucketsUpdatePredefinedDefaultObjectACL

data BucketsUpdatePredefinedDefaultObjectACL Source #

Apply a predefined set of default object access controls to this bucket.

Constructors

AuthenticatedRead

authenticatedRead Object owner gets OWNER access, and allAuthenticatedUsers get READER access.

BucketOwnerFullControl

bucketOwnerFullControl Object owner gets OWNER access, and project team owners get OWNER access.

BucketOwnerRead

bucketOwnerRead Object owner gets OWNER access, and project team owners get READER access.

Private

private Object owner gets OWNER access.

ProjectPrivate

projectPrivate Object owner gets OWNER access, and project team members get access according to their roles.

PublicRead

publicRead Object owner gets OWNER access, and allUsers get READER access.

Instances

Enum BucketsUpdatePredefinedDefaultObjectACL Source # 
Eq BucketsUpdatePredefinedDefaultObjectACL Source # 
Data BucketsUpdatePredefinedDefaultObjectACL Source # 

Methods

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

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

toConstr :: BucketsUpdatePredefinedDefaultObjectACL -> Constr #

dataTypeOf :: BucketsUpdatePredefinedDefaultObjectACL -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord BucketsUpdatePredefinedDefaultObjectACL Source # 
Read BucketsUpdatePredefinedDefaultObjectACL Source # 
Show BucketsUpdatePredefinedDefaultObjectACL Source # 
Generic BucketsUpdatePredefinedDefaultObjectACL Source # 
Hashable BucketsUpdatePredefinedDefaultObjectACL Source # 
ToJSON BucketsUpdatePredefinedDefaultObjectACL Source # 
FromJSON BucketsUpdatePredefinedDefaultObjectACL Source # 
FromHttpApiData BucketsUpdatePredefinedDefaultObjectACL Source # 
ToHttpApiData BucketsUpdatePredefinedDefaultObjectACL Source # 
type Rep BucketsUpdatePredefinedDefaultObjectACL Source # 
type Rep BucketsUpdatePredefinedDefaultObjectACL = D1 (MetaData "BucketsUpdatePredefinedDefaultObjectACL" "Network.Google.Storage.Types.Sum" "gogol-storage-0.3.0-DGwRnfj7WmaH5CaBqC8AR9" False) ((:+:) ((:+:) (C1 (MetaCons "AuthenticatedRead" PrefixI False) U1) ((:+:) (C1 (MetaCons "BucketOwnerFullControl" PrefixI False) U1) (C1 (MetaCons "BucketOwnerRead" PrefixI False) U1))) ((:+:) (C1 (MetaCons "Private" PrefixI False) U1) ((:+:) (C1 (MetaCons "ProjectPrivate" PrefixI False) U1) (C1 (MetaCons "PublicRead" PrefixI False) U1))))

ObjectsComposeDestinationPredefinedACL

data ObjectsComposeDestinationPredefinedACL Source #

Apply a predefined set of access controls to the destination object.

Constructors

OCDPAAuthenticatedRead

authenticatedRead Object owner gets OWNER access, and allAuthenticatedUsers get READER access.

OCDPABucketOwnerFullControl

bucketOwnerFullControl Object owner gets OWNER access, and project team owners get OWNER access.

OCDPABucketOwnerRead

bucketOwnerRead Object owner gets OWNER access, and project team owners get READER access.

OCDPAPrivate

private Object owner gets OWNER access.

OCDPAProjectPrivate

projectPrivate Object owner gets OWNER access, and project team members get access according to their roles.

OCDPAPublicRead

publicRead Object owner gets OWNER access, and allUsers get READER access.

Instances

Enum ObjectsComposeDestinationPredefinedACL Source # 
Eq ObjectsComposeDestinationPredefinedACL Source # 
Data ObjectsComposeDestinationPredefinedACL Source # 

Methods

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

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

toConstr :: ObjectsComposeDestinationPredefinedACL -> Constr #

dataTypeOf :: ObjectsComposeDestinationPredefinedACL -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ObjectsComposeDestinationPredefinedACL Source # 
Read ObjectsComposeDestinationPredefinedACL Source # 
Show ObjectsComposeDestinationPredefinedACL Source # 
Generic ObjectsComposeDestinationPredefinedACL Source # 
Hashable ObjectsComposeDestinationPredefinedACL Source # 
ToJSON ObjectsComposeDestinationPredefinedACL Source # 
FromJSON ObjectsComposeDestinationPredefinedACL Source # 
FromHttpApiData ObjectsComposeDestinationPredefinedACL Source # 
ToHttpApiData ObjectsComposeDestinationPredefinedACL Source # 
type Rep ObjectsComposeDestinationPredefinedACL Source # 
type Rep ObjectsComposeDestinationPredefinedACL = D1 (MetaData "ObjectsComposeDestinationPredefinedACL" "Network.Google.Storage.Types.Sum" "gogol-storage-0.3.0-DGwRnfj7WmaH5CaBqC8AR9" False) ((:+:) ((:+:) (C1 (MetaCons "OCDPAAuthenticatedRead" PrefixI False) U1) ((:+:) (C1 (MetaCons "OCDPABucketOwnerFullControl" PrefixI False) U1) (C1 (MetaCons "OCDPABucketOwnerRead" PrefixI False) U1))) ((:+:) (C1 (MetaCons "OCDPAPrivate" PrefixI False) U1) ((:+:) (C1 (MetaCons "OCDPAProjectPrivate" PrefixI False) U1) (C1 (MetaCons "OCDPAPublicRead" PrefixI False) U1))))

BucketsInsertPredefinedACL

data BucketsInsertPredefinedACL Source #

Apply a predefined set of access controls to this bucket.

Constructors

BIPAAuthenticatedRead

authenticatedRead Project team owners get OWNER access, and allAuthenticatedUsers get READER access.

BIPAPrivate

private Project team owners get OWNER access.

BIPAProjectPrivate

projectPrivate Project team members get access according to their roles.

BIPAPublicRead

publicRead Project team owners get OWNER access, and allUsers get READER access.

BIPAPublicReadWrite

publicReadWrite Project team owners get OWNER access, and allUsers get WRITER access.

Instances

Enum BucketsInsertPredefinedACL Source # 
Eq BucketsInsertPredefinedACL Source # 
Data BucketsInsertPredefinedACL Source # 

Methods

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

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

toConstr :: BucketsInsertPredefinedACL -> Constr #

dataTypeOf :: BucketsInsertPredefinedACL -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord BucketsInsertPredefinedACL Source # 
Read BucketsInsertPredefinedACL Source # 
Show BucketsInsertPredefinedACL Source # 
Generic BucketsInsertPredefinedACL Source # 
Hashable BucketsInsertPredefinedACL Source # 
ToJSON BucketsInsertPredefinedACL Source # 
FromJSON BucketsInsertPredefinedACL Source # 
FromHttpApiData BucketsInsertPredefinedACL Source # 
ToHttpApiData BucketsInsertPredefinedACL Source # 
type Rep BucketsInsertPredefinedACL Source # 
type Rep BucketsInsertPredefinedACL = D1 (MetaData "BucketsInsertPredefinedACL" "Network.Google.Storage.Types.Sum" "gogol-storage-0.3.0-DGwRnfj7WmaH5CaBqC8AR9" False) ((:+:) ((:+:) (C1 (MetaCons "BIPAAuthenticatedRead" PrefixI False) U1) (C1 (MetaCons "BIPAPrivate" PrefixI False) U1)) ((:+:) (C1 (MetaCons "BIPAProjectPrivate" PrefixI False) U1) ((:+:) (C1 (MetaCons "BIPAPublicRead" PrefixI False) U1) (C1 (MetaCons "BIPAPublicReadWrite" PrefixI False) U1))))

Buckets

data Buckets Source #

A list of buckets.

See: buckets smart constructor.

Instances

Eq Buckets Source # 

Methods

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

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

Data Buckets Source # 

Methods

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

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

toConstr :: Buckets -> Constr #

dataTypeOf :: Buckets -> DataType #

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

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

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

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

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

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

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

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

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

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

Show Buckets Source # 
Generic Buckets Source # 

Associated Types

type Rep Buckets :: * -> * #

Methods

from :: Buckets -> Rep Buckets x #

to :: Rep Buckets x -> Buckets #

ToJSON Buckets Source # 
FromJSON Buckets Source # 
type Rep Buckets Source # 
type Rep Buckets = D1 (MetaData "Buckets" "Network.Google.Storage.Types.Product" "gogol-storage-0.3.0-DGwRnfj7WmaH5CaBqC8AR9" False) (C1 (MetaCons "Buckets'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_bNextPageToken") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_bKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "_bItems") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Bucket]))))))

buckets :: Buckets Source #

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

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

bNextPageToken :: Lens' Buckets (Maybe Text) Source #

The continuation token, used to page through large result sets. Provide this value in a subsequent request to return the next page of results.

bKind :: Lens' Buckets Text Source #

The kind of item this is. For lists of buckets, this is always storage#buckets.

bItems :: Lens' Buckets [Bucket] Source #

The list of items.

BucketLogging

data BucketLogging Source #

The bucket's logging configuration, which defines the destination bucket and optional name prefix for the current bucket's logs.

See: bucketLogging smart constructor.

Instances

Eq BucketLogging Source # 
Data BucketLogging Source # 

Methods

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

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

toConstr :: BucketLogging -> Constr #

dataTypeOf :: BucketLogging -> DataType #

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

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

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

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

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

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

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

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

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

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

Show BucketLogging Source # 
Generic BucketLogging Source # 

Associated Types

type Rep BucketLogging :: * -> * #

ToJSON BucketLogging Source # 
FromJSON BucketLogging Source # 
type Rep BucketLogging Source # 
type Rep BucketLogging = D1 (MetaData "BucketLogging" "Network.Google.Storage.Types.Product" "gogol-storage-0.3.0-DGwRnfj7WmaH5CaBqC8AR9" False) (C1 (MetaCons "BucketLogging'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_blLogBucket") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_blLogObjectPrefix") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))

bucketLogging :: BucketLogging Source #

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

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

blLogBucket :: Lens' BucketLogging (Maybe Text) Source #

The destination bucket where the current bucket's logs should be placed.

blLogObjectPrefix :: Lens' BucketLogging (Maybe Text) Source #

A prefix for log object names.

ObjectMetadata

data ObjectMetadata Source #

User-provided metadata, in key/value pairs.

See: objectMetadata smart constructor.

Instances

Eq ObjectMetadata Source # 
Data ObjectMetadata Source # 

Methods

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

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

toConstr :: ObjectMetadata -> Constr #

dataTypeOf :: ObjectMetadata -> DataType #

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

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

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

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

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

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

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

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

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

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

Show ObjectMetadata Source # 
Generic ObjectMetadata Source # 

Associated Types

type Rep ObjectMetadata :: * -> * #

ToJSON ObjectMetadata Source # 
FromJSON ObjectMetadata Source # 
type Rep ObjectMetadata Source # 
type Rep ObjectMetadata = D1 (MetaData "ObjectMetadata" "Network.Google.Storage.Types.Product" "gogol-storage-0.3.0-DGwRnfj7WmaH5CaBqC8AR9" True) (C1 (MetaCons "ObjectMetadata'" PrefixI True) (S1 (MetaSel (Just Symbol "_omAddtional") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (HashMap Text Text))))

objectMetadata Source #

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

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

omAddtional :: Lens' ObjectMetadata (HashMap Text Text) Source #

An individual metadata entry.

ObjectsPatchPredefinedACL

data ObjectsPatchPredefinedACL Source #

Apply a predefined set of access controls to this object.

Constructors

OPPAAuthenticatedRead

authenticatedRead Object owner gets OWNER access, and allAuthenticatedUsers get READER access.

OPPABucketOwnerFullControl

bucketOwnerFullControl Object owner gets OWNER access, and project team owners get OWNER access.

OPPABucketOwnerRead

bucketOwnerRead Object owner gets OWNER access, and project team owners get READER access.

OPPAPrivate

private Object owner gets OWNER access.

OPPAProjectPrivate

projectPrivate Object owner gets OWNER access, and project team members get access according to their roles.

OPPAPublicRead

publicRead Object owner gets OWNER access, and allUsers get READER access.

Instances

Enum ObjectsPatchPredefinedACL Source # 
Eq ObjectsPatchPredefinedACL Source # 
Data ObjectsPatchPredefinedACL Source # 

Methods

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

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

toConstr :: ObjectsPatchPredefinedACL -> Constr #

dataTypeOf :: ObjectsPatchPredefinedACL -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ObjectsPatchPredefinedACL Source # 
Read ObjectsPatchPredefinedACL Source # 
Show ObjectsPatchPredefinedACL Source # 
Generic ObjectsPatchPredefinedACL Source # 
Hashable ObjectsPatchPredefinedACL Source # 
ToJSON ObjectsPatchPredefinedACL Source # 
FromJSON ObjectsPatchPredefinedACL Source # 
FromHttpApiData ObjectsPatchPredefinedACL Source # 
ToHttpApiData ObjectsPatchPredefinedACL Source # 
type Rep ObjectsPatchPredefinedACL Source # 
type Rep ObjectsPatchPredefinedACL = D1 (MetaData "ObjectsPatchPredefinedACL" "Network.Google.Storage.Types.Sum" "gogol-storage-0.3.0-DGwRnfj7WmaH5CaBqC8AR9" False) ((:+:) ((:+:) (C1 (MetaCons "OPPAAuthenticatedRead" PrefixI False) U1) ((:+:) (C1 (MetaCons "OPPABucketOwnerFullControl" PrefixI False) U1) (C1 (MetaCons "OPPABucketOwnerRead" PrefixI False) U1))) ((:+:) (C1 (MetaCons "OPPAPrivate" PrefixI False) U1) ((:+:) (C1 (MetaCons "OPPAProjectPrivate" PrefixI False) U1) (C1 (MetaCons "OPPAPublicRead" PrefixI False) U1))))

BucketLifecycleRuleItemCondition

data BucketLifecycleRuleItemCondition Source #

The condition(s) under which the action will be taken.

See: bucketLifecycleRuleItemCondition smart constructor.

Instances

Eq BucketLifecycleRuleItemCondition Source # 
Data BucketLifecycleRuleItemCondition Source # 

Methods

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

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

toConstr :: BucketLifecycleRuleItemCondition -> Constr #

dataTypeOf :: BucketLifecycleRuleItemCondition -> DataType #

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

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

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

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

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

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

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

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

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

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

Show BucketLifecycleRuleItemCondition Source # 
Generic BucketLifecycleRuleItemCondition Source # 
ToJSON BucketLifecycleRuleItemCondition Source # 
FromJSON BucketLifecycleRuleItemCondition Source # 
type Rep BucketLifecycleRuleItemCondition Source # 
type Rep BucketLifecycleRuleItemCondition = D1 (MetaData "BucketLifecycleRuleItemCondition" "Network.Google.Storage.Types.Product" "gogol-storage-0.3.0-DGwRnfj7WmaH5CaBqC8AR9" False) (C1 (MetaCons "BucketLifecycleRuleItemCondition'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_blricAge") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32)))) (S1 (MetaSel (Just Symbol "_blricIsLive") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool)))) ((:*:) (S1 (MetaSel (Just Symbol "_blricNumNewerVersions") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32)))) ((:*:) (S1 (MetaSel (Just Symbol "_blricMatchesStorageClass") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Text]))) (S1 (MetaSel (Just Symbol "_blricCreatedBefore") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Date')))))))

bucketLifecycleRuleItemCondition :: BucketLifecycleRuleItemCondition Source #

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

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

blricAge :: Lens' BucketLifecycleRuleItemCondition (Maybe Int32) Source #

Age of an object (in days). This condition is satisfied when an object reaches the specified age.

blricIsLive :: Lens' BucketLifecycleRuleItemCondition (Maybe Bool) Source #

Relevant only for versioned objects. If the value is true, this condition matches live objects; if the value is false, it matches archived objects.

blricNumNewerVersions :: Lens' BucketLifecycleRuleItemCondition (Maybe Int32) Source #

Relevant only for versioned objects. If the value is N, this condition is satisfied when there are at least N versions (including the live version) newer than this version of the object.

blricMatchesStorageClass :: Lens' BucketLifecycleRuleItemCondition [Text] Source #

Objects having any of the storage classes specified by this condition will be matched. Values include MULTI_REGIONAL, REGIONAL, NEARLINE, COLDLINE, STANDARD, and DURABLE_REDUCED_AVAILABILITY.

blricCreatedBefore :: Lens' BucketLifecycleRuleItemCondition (Maybe Day) Source #

A date in RFC 3339 format with only the date part (for instance, "2013-01-15"). This condition is satisfied when an object is created before midnight of the specified date in UTC.

ObjectsRewriteDestinationPredefinedACL

data ObjectsRewriteDestinationPredefinedACL Source #

Apply a predefined set of access controls to the destination object.

Constructors

ORDPAAuthenticatedRead

authenticatedRead Object owner gets OWNER access, and allAuthenticatedUsers get READER access.

ORDPABucketOwnerFullControl

bucketOwnerFullControl Object owner gets OWNER access, and project team owners get OWNER access.

ORDPABucketOwnerRead

bucketOwnerRead Object owner gets OWNER access, and project team owners get READER access.

ORDPAPrivate

private Object owner gets OWNER access.

ORDPAProjectPrivate

projectPrivate Object owner gets OWNER access, and project team members get access according to their roles.

ORDPAPublicRead

publicRead Object owner gets OWNER access, and allUsers get READER access.

Instances

Enum ObjectsRewriteDestinationPredefinedACL Source # 
Eq ObjectsRewriteDestinationPredefinedACL Source # 
Data ObjectsRewriteDestinationPredefinedACL Source # 

Methods

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

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

toConstr :: ObjectsRewriteDestinationPredefinedACL -> Constr #

dataTypeOf :: ObjectsRewriteDestinationPredefinedACL -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ObjectsRewriteDestinationPredefinedACL Source # 
Read ObjectsRewriteDestinationPredefinedACL Source # 
Show ObjectsRewriteDestinationPredefinedACL Source # 
Generic ObjectsRewriteDestinationPredefinedACL Source # 
Hashable ObjectsRewriteDestinationPredefinedACL Source # 
ToJSON ObjectsRewriteDestinationPredefinedACL Source # 
FromJSON ObjectsRewriteDestinationPredefinedACL Source # 
FromHttpApiData ObjectsRewriteDestinationPredefinedACL Source # 
ToHttpApiData ObjectsRewriteDestinationPredefinedACL Source # 
type Rep ObjectsRewriteDestinationPredefinedACL Source # 
type Rep ObjectsRewriteDestinationPredefinedACL = D1 (MetaData "ObjectsRewriteDestinationPredefinedACL" "Network.Google.Storage.Types.Sum" "gogol-storage-0.3.0-DGwRnfj7WmaH5CaBqC8AR9" False) ((:+:) ((:+:) (C1 (MetaCons "ORDPAAuthenticatedRead" PrefixI False) U1) ((:+:) (C1 (MetaCons "ORDPABucketOwnerFullControl" PrefixI False) U1) (C1 (MetaCons "ORDPABucketOwnerRead" PrefixI False) U1))) ((:+:) (C1 (MetaCons "ORDPAPrivate" PrefixI False) U1) ((:+:) (C1 (MetaCons "ORDPAProjectPrivate" PrefixI False) U1) (C1 (MetaCons "ORDPAPublicRead" PrefixI False) U1))))

BucketLifecycle

data BucketLifecycle Source #

The bucket's lifecycle configuration. See lifecycle management for more information.

See: bucketLifecycle smart constructor.

Instances

Eq BucketLifecycle Source # 
Data BucketLifecycle Source # 

Methods

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

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

toConstr :: BucketLifecycle -> Constr #

dataTypeOf :: BucketLifecycle -> DataType #

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

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

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

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

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

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

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

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

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

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

Show BucketLifecycle Source # 
Generic BucketLifecycle Source # 
ToJSON BucketLifecycle Source # 
FromJSON BucketLifecycle Source # 
type Rep BucketLifecycle Source # 
type Rep BucketLifecycle = D1 (MetaData "BucketLifecycle" "Network.Google.Storage.Types.Product" "gogol-storage-0.3.0-DGwRnfj7WmaH5CaBqC8AR9" True) (C1 (MetaCons "BucketLifecycle'" PrefixI True) (S1 (MetaSel (Just Symbol "_blRule") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe [BucketLifecycleRuleItem]))))

bucketLifecycle :: BucketLifecycle Source #

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

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

blRule :: Lens' BucketLifecycle [BucketLifecycleRuleItem] Source #

A lifecycle management rule, which is made of an action to take and the condition(s) under which the action will be taken.

Channel

data Channel Source #

An notification channel used to watch for resource changes.

See: channel smart constructor.

Instances

Eq Channel Source # 

Methods

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

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

Data Channel Source # 

Methods

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

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

toConstr :: Channel -> Constr #

dataTypeOf :: Channel -> DataType #

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

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

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

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

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

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

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

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

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

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

Show Channel Source # 
Generic Channel Source # 

Associated Types

type Rep Channel :: * -> * #

Methods

from :: Channel -> Rep Channel x #

to :: Rep Channel x -> Channel #

ToJSON Channel Source # 
FromJSON Channel Source # 
type Rep Channel Source # 

channel :: Channel Source #

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

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

cResourceURI :: Lens' Channel (Maybe Text) Source #

A version-specific identifier for the watched resource.

cResourceId :: Lens' Channel (Maybe Text) Source #

An opaque ID that identifies the resource being watched on this channel. Stable across different API versions.

cKind :: Lens' Channel Text Source #

Identifies this as a notification channel used to watch for changes to a resource. Value: the fixed string "api#channel".

cExpiration :: Lens' Channel (Maybe Int64) Source #

Date and time of notification channel expiration, expressed as a Unix timestamp, in milliseconds. Optional.

cToken :: Lens' Channel (Maybe Text) Source #

An arbitrary string delivered to the target address with each notification delivered over this channel. Optional.

cAddress :: Lens' Channel (Maybe Text) Source #

The address where notifications are delivered for this channel.

cPayload :: Lens' Channel (Maybe Bool) Source #

A Boolean value to indicate whether payload is wanted. Optional.

cParams :: Lens' Channel (Maybe ChannelParams) Source #

Additional parameters controlling delivery channel behavior. Optional.

cId :: Lens' Channel (Maybe Text) Source #

A UUID or similar unique string that identifies this channel.

cType :: Lens' Channel (Maybe Text) Source #

The type of delivery mechanism used for this channel.

BucketLifecycleRuleItem

data BucketLifecycleRuleItem Source #

Instances

Eq BucketLifecycleRuleItem Source # 
Data BucketLifecycleRuleItem Source # 

Methods

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

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

toConstr :: BucketLifecycleRuleItem -> Constr #

dataTypeOf :: BucketLifecycleRuleItem -> DataType #

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

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

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

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

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

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

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

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

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

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

Show BucketLifecycleRuleItem Source # 
Generic BucketLifecycleRuleItem Source # 
ToJSON BucketLifecycleRuleItem Source # 
FromJSON BucketLifecycleRuleItem Source # 
type Rep BucketLifecycleRuleItem Source # 
type Rep BucketLifecycleRuleItem = D1 (MetaData "BucketLifecycleRuleItem" "Network.Google.Storage.Types.Product" "gogol-storage-0.3.0-DGwRnfj7WmaH5CaBqC8AR9" False) (C1 (MetaCons "BucketLifecycleRuleItem'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_blriAction") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe BucketLifecycleRuleItemAction))) (S1 (MetaSel (Just Symbol "_blriCondition") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe BucketLifecycleRuleItemCondition)))))

bucketLifecycleRuleItem :: BucketLifecycleRuleItem Source #

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

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

blriCondition :: Lens' BucketLifecycleRuleItem (Maybe BucketLifecycleRuleItemCondition) Source #

The condition(s) under which the action will be taken.

ObjectsWatchAllProjection

data ObjectsWatchAllProjection Source #

Set of properties to return. Defaults to noAcl.

Constructors

OWAPFull

full Include all properties.

OWAPNoACL

noAcl Omit the owner, acl property.

Instances

Enum ObjectsWatchAllProjection Source # 
Eq ObjectsWatchAllProjection Source # 
Data ObjectsWatchAllProjection Source # 

Methods

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

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

toConstr :: ObjectsWatchAllProjection -> Constr #

dataTypeOf :: ObjectsWatchAllProjection -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ObjectsWatchAllProjection Source # 
Read ObjectsWatchAllProjection Source # 
Show ObjectsWatchAllProjection Source # 
Generic ObjectsWatchAllProjection Source # 
Hashable ObjectsWatchAllProjection Source # 
ToJSON ObjectsWatchAllProjection Source # 
FromJSON ObjectsWatchAllProjection Source # 
FromHttpApiData ObjectsWatchAllProjection Source # 
ToHttpApiData ObjectsWatchAllProjection Source # 
type Rep ObjectsWatchAllProjection Source # 
type Rep ObjectsWatchAllProjection = D1 (MetaData "ObjectsWatchAllProjection" "Network.Google.Storage.Types.Sum" "gogol-storage-0.3.0-DGwRnfj7WmaH5CaBqC8AR9" False) ((:+:) (C1 (MetaCons "OWAPFull" PrefixI False) U1) (C1 (MetaCons "OWAPNoACL" PrefixI False) U1))

BucketCORSItem

data BucketCORSItem Source #

Instances

Eq BucketCORSItem Source # 
Data BucketCORSItem Source # 

Methods

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

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

toConstr :: BucketCORSItem -> Constr #

dataTypeOf :: BucketCORSItem -> DataType #

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

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

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

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

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

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

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

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

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

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

Show BucketCORSItem Source # 
Generic BucketCORSItem Source # 

Associated Types

type Rep BucketCORSItem :: * -> * #

ToJSON BucketCORSItem Source # 
FromJSON BucketCORSItem Source # 
type Rep BucketCORSItem Source # 
type Rep BucketCORSItem = D1 (MetaData "BucketCORSItem" "Network.Google.Storage.Types.Product" "gogol-storage-0.3.0-DGwRnfj7WmaH5CaBqC8AR9" False) (C1 (MetaCons "BucketCORSItem'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_bciMaxAgeSeconds") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32)))) (S1 (MetaSel (Just Symbol "_bciOrigin") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Text])))) ((:*:) (S1 (MetaSel (Just Symbol "_bciResponseHeader") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Text]))) (S1 (MetaSel (Just Symbol "_bciMethod") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Text]))))))

bucketCORSItem :: BucketCORSItem Source #

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

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

bciMaxAgeSeconds :: Lens' BucketCORSItem (Maybe Int32) Source #

The value, in seconds, to return in the Access-Control-Max-Age header used in preflight responses.

bciOrigin :: Lens' BucketCORSItem [Text] Source #

The list of Origins eligible to receive CORS response headers. Note: "*" is permitted in the list of origins, and means "any Origin".

bciResponseHeader :: Lens' BucketCORSItem [Text] Source #

The list of HTTP headers other than the simple response headers to give permission for the user-agent to share across domains.

bciMethod :: Lens' BucketCORSItem [Text] Source #

The list of HTTP methods on which to include CORS response headers, (GET, OPTIONS, POST, etc) Note: "*" is permitted in the list of methods, and means "any method".

ObjectAccessControlProjectTeam

data ObjectAccessControlProjectTeam Source #

The project team associated with the entity, if any.

See: objectAccessControlProjectTeam smart constructor.

Instances

Eq ObjectAccessControlProjectTeam Source # 
Data ObjectAccessControlProjectTeam Source # 

Methods

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

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

toConstr :: ObjectAccessControlProjectTeam -> Constr #

dataTypeOf :: ObjectAccessControlProjectTeam -> DataType #

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

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

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

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

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

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

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

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

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

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

Show ObjectAccessControlProjectTeam Source # 
Generic ObjectAccessControlProjectTeam Source # 
ToJSON ObjectAccessControlProjectTeam Source # 
FromJSON ObjectAccessControlProjectTeam Source # 
type Rep ObjectAccessControlProjectTeam Source # 
type Rep ObjectAccessControlProjectTeam = D1 (MetaData "ObjectAccessControlProjectTeam" "Network.Google.Storage.Types.Product" "gogol-storage-0.3.0-DGwRnfj7WmaH5CaBqC8AR9" False) (C1 (MetaCons "ObjectAccessControlProjectTeam'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_oacptProjectNumber") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_oacptTeam") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))

objectAccessControlProjectTeam :: ObjectAccessControlProjectTeam Source #

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

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

ObjectCustomerEncryption

data ObjectCustomerEncryption Source #

Metadata of customer-supplied encryption key, if the object is encrypted by such a key.

See: objectCustomerEncryption smart constructor.

Instances

Eq ObjectCustomerEncryption Source # 
Data ObjectCustomerEncryption Source # 

Methods

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

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

toConstr :: ObjectCustomerEncryption -> Constr #

dataTypeOf :: ObjectCustomerEncryption -> DataType #

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

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

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

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

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

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

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

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

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

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

Show ObjectCustomerEncryption Source # 
Generic ObjectCustomerEncryption Source # 
ToJSON ObjectCustomerEncryption Source # 
FromJSON ObjectCustomerEncryption Source # 
type Rep ObjectCustomerEncryption Source # 
type Rep ObjectCustomerEncryption = D1 (MetaData "ObjectCustomerEncryption" "Network.Google.Storage.Types.Product" "gogol-storage-0.3.0-DGwRnfj7WmaH5CaBqC8AR9" False) (C1 (MetaCons "ObjectCustomerEncryption'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_oceKeySha256") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_oceEncryptionAlgorithm") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))

objectCustomerEncryption :: ObjectCustomerEncryption Source #

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

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

oceKeySha256 :: Lens' ObjectCustomerEncryption (Maybe Text) Source #

SHA256 hash value of the encryption key.

Bucket

data Bucket Source #

A bucket.

See: bucket smart constructor.

Instances

Eq Bucket Source # 

Methods

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

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

Data Bucket Source # 

Methods

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

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

toConstr :: Bucket -> Constr #

dataTypeOf :: Bucket -> DataType #

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

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

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

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

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

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

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

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

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

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

Show Bucket Source # 
Generic Bucket Source # 

Associated Types

type Rep Bucket :: * -> * #

Methods

from :: Bucket -> Rep Bucket x #

to :: Rep Bucket x -> Bucket #

ToJSON Bucket Source # 
FromJSON Bucket Source # 
type Rep Bucket Source # 
type Rep Bucket = D1 (MetaData "Bucket" "Network.Google.Storage.Types.Product" "gogol-storage-0.3.0-DGwRnfj7WmaH5CaBqC8AR9" False) (C1 (MetaCons "Bucket'" PrefixI True) ((:*:) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_bucEtag") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_bucLocation") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_bucKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "_bucWebsite") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe BucketWebsite))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_bucProjectNumber") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Word64)))) (S1 (MetaSel (Just Symbol "_bucLifecycle") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe BucketLifecycle)))) ((:*:) (S1 (MetaSel (Just Symbol "_bucOwner") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe BucketOwner))) ((:*:) (S1 (MetaSel (Just Symbol "_bucSelfLink") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_bucName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))))) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_bucStorageClass") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_bucVersioning") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe BucketVersioning)))) ((:*:) (S1 (MetaSel (Just Symbol "_bucCORS") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [BucketCORSItem]))) ((:*:) (S1 (MetaSel (Just Symbol "_bucTimeCreated") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DateTime'))) (S1 (MetaSel (Just Symbol "_bucId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_bucUpdated") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DateTime'))) (S1 (MetaSel (Just Symbol "_bucDefaultObjectACL") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [ObjectAccessControl])))) ((:*:) (S1 (MetaSel (Just Symbol "_bucMetageneration") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) ((:*:) (S1 (MetaSel (Just Symbol "_bucLogging") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe BucketLogging))) (S1 (MetaSel (Just Symbol "_bucACL") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [BucketAccessControl])))))))))

bucEtag :: Lens' Bucket (Maybe Text) Source #

HTTP 1.1 Entity tag for the bucket.

bucLocation :: Lens' Bucket (Maybe Text) Source #

The location of the bucket. Object data for objects in the bucket resides in physical storage within this region. Defaults to US. See the developer's guide for the authoritative list.

bucKind :: Lens' Bucket Text Source #

The kind of item this is. For buckets, this is always storage#bucket.

bucWebsite :: Lens' Bucket (Maybe BucketWebsite) Source #

The bucket's website configuration, controlling how the service behaves when accessing bucket contents as a web site. See the Static Website Examples for more information.

bucProjectNumber :: Lens' Bucket (Maybe Word64) Source #

The project number of the project the bucket belongs to.

bucLifecycle :: Lens' Bucket (Maybe BucketLifecycle) Source #

The bucket's lifecycle configuration. See lifecycle management for more information.

bucOwner :: Lens' Bucket (Maybe BucketOwner) Source #

The owner of the bucket. This is always the project team's owner group.

bucSelfLink :: Lens' Bucket (Maybe Text) Source #

The URI of this bucket.

bucName :: Lens' Bucket (Maybe Text) Source #

The name of the bucket.

bucStorageClass :: Lens' Bucket (Maybe Text) Source #

The bucket's default storage class, used whenever no storageClass is specified for a newly-created object. This defines how objects in the bucket are stored and determines the SLA and the cost of storage. Values include MULTI_REGIONAL, REGIONAL, STANDARD, NEARLINE, COLDLINE, and DURABLE_REDUCED_AVAILABILITY. If this value is not specified when the bucket is created, it will default to STANDARD. For more information, see storage classes.

bucVersioning :: Lens' Bucket (Maybe BucketVersioning) Source #

The bucket's versioning configuration.

bucCORS :: Lens' Bucket [BucketCORSItem] Source #

The bucket's Cross-Origin Resource Sharing (CORS) configuration.

bucTimeCreated :: Lens' Bucket (Maybe UTCTime) Source #

The creation time of the bucket in RFC 3339 format.

bucId :: Lens' Bucket (Maybe Text) Source #

The ID of the bucket.

bucUpdated :: Lens' Bucket (Maybe UTCTime) Source #

The modification time of the bucket in RFC 3339 format.

bucDefaultObjectACL :: Lens' Bucket [ObjectAccessControl] Source #

Default access controls to apply to new objects when no ACL is provided.

bucMetageneration :: Lens' Bucket (Maybe Int64) Source #

The metadata generation of this bucket.

bucLogging :: Lens' Bucket (Maybe BucketLogging) Source #

The bucket's logging configuration, which defines the destination bucket and optional name prefix for the current bucket's logs.

bucACL :: Lens' Bucket [BucketAccessControl] Source #

Access controls on the bucket.

BucketsGetProjection

data BucketsGetProjection Source #

Set of properties to return. Defaults to noAcl.

Constructors

BGPFull

full Include all properties.

BGPNoACL

noAcl Omit owner, acl and defaultObjectAcl properties.

Instances

Enum BucketsGetProjection Source # 
Eq BucketsGetProjection Source # 
Data BucketsGetProjection Source # 

Methods

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

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

toConstr :: BucketsGetProjection -> Constr #

dataTypeOf :: BucketsGetProjection -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord BucketsGetProjection Source # 
Read BucketsGetProjection Source # 
Show BucketsGetProjection Source # 
Generic BucketsGetProjection Source # 
Hashable BucketsGetProjection Source # 
ToJSON BucketsGetProjection Source # 
FromJSON BucketsGetProjection Source # 
FromHttpApiData BucketsGetProjection Source # 
ToHttpApiData BucketsGetProjection Source # 
type Rep BucketsGetProjection Source # 
type Rep BucketsGetProjection = D1 (MetaData "BucketsGetProjection" "Network.Google.Storage.Types.Sum" "gogol-storage-0.3.0-DGwRnfj7WmaH5CaBqC8AR9" False) ((:+:) (C1 (MetaCons "BGPFull" PrefixI False) U1) (C1 (MetaCons "BGPNoACL" PrefixI False) U1))

Objects

data Objects Source #

A list of objects.

See: objects smart constructor.

Instances

Eq Objects Source # 

Methods

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

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

Data Objects Source # 

Methods

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

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

toConstr :: Objects -> Constr #

dataTypeOf :: Objects -> DataType #

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

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

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

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

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

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

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

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

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

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

Show Objects Source # 
Generic Objects Source # 

Associated Types

type Rep Objects :: * -> * #

Methods

from :: Objects -> Rep Objects x #

to :: Rep Objects x -> Objects #

ToJSON Objects Source # 
FromJSON Objects Source # 
type Rep Objects Source # 
type Rep Objects = D1 (MetaData "Objects" "Network.Google.Storage.Types.Product" "gogol-storage-0.3.0-DGwRnfj7WmaH5CaBqC8AR9" False) (C1 (MetaCons "Objects'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_oNextPageToken") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_oKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text))) ((:*:) (S1 (MetaSel (Just Symbol "_oItems") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Object]))) (S1 (MetaSel (Just Symbol "_oPrefixes") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Text]))))))

objects :: Objects Source #

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

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

oNextPageToken :: Lens' Objects (Maybe Text) Source #

The continuation token, used to page through large result sets. Provide this value in a subsequent request to return the next page of results.

oKind :: Lens' Objects Text Source #

The kind of item this is. For lists of objects, this is always storage#objects.

oItems :: Lens' Objects [Object] Source #

The list of items.

oPrefixes :: Lens' Objects [Text] Source #

The list of prefixes of objects matching-but-not-listed up to and including the requested delimiter.

BucketsPatchProjection

data BucketsPatchProjection Source #

Set of properties to return. Defaults to full.

Constructors

BPPFull

full Include all properties.

BPPNoACL

noAcl Omit owner, acl and defaultObjectAcl properties.

Instances

Enum BucketsPatchProjection Source # 
Eq BucketsPatchProjection Source # 
Data BucketsPatchProjection Source # 

Methods

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

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

toConstr :: BucketsPatchProjection -> Constr #

dataTypeOf :: BucketsPatchProjection -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord BucketsPatchProjection Source # 
Read BucketsPatchProjection Source # 
Show BucketsPatchProjection Source # 
Generic BucketsPatchProjection Source # 
Hashable BucketsPatchProjection Source # 
ToJSON BucketsPatchProjection Source # 
FromJSON BucketsPatchProjection Source # 
FromHttpApiData BucketsPatchProjection Source # 
ToHttpApiData BucketsPatchProjection Source # 
type Rep BucketsPatchProjection Source # 
type Rep BucketsPatchProjection = D1 (MetaData "BucketsPatchProjection" "Network.Google.Storage.Types.Sum" "gogol-storage-0.3.0-DGwRnfj7WmaH5CaBqC8AR9" False) ((:+:) (C1 (MetaCons "BPPFull" PrefixI False) U1) (C1 (MetaCons "BPPNoACL" PrefixI False) U1))

BucketAccessControls

data BucketAccessControls Source #

An access-control list.

See: bucketAccessControls smart constructor.

Instances

Eq BucketAccessControls Source # 
Data BucketAccessControls Source # 

Methods

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

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

toConstr :: BucketAccessControls -> Constr #

dataTypeOf :: BucketAccessControls -> DataType #

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

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

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

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

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

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

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

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

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

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

Show BucketAccessControls Source # 
Generic BucketAccessControls Source # 
ToJSON BucketAccessControls Source # 
FromJSON BucketAccessControls Source # 
type Rep BucketAccessControls Source # 
type Rep BucketAccessControls = D1 (MetaData "BucketAccessControls" "Network.Google.Storage.Types.Product" "gogol-storage-0.3.0-DGwRnfj7WmaH5CaBqC8AR9" False) (C1 (MetaCons "BucketAccessControls'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_bacKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "_bacItems") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [BucketAccessControl])))))

bucketAccessControls :: BucketAccessControls Source #

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

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

bacKind :: Lens' BucketAccessControls Text Source #

The kind of item this is. For lists of bucket access control entries, this is always storage#bucketAccessControls.

BucketsUpdateProjection

data BucketsUpdateProjection Source #

Set of properties to return. Defaults to full.

Constructors

BUPFull

full Include all properties.

BUPNoACL

noAcl Omit owner, acl and defaultObjectAcl properties.

Instances

Enum BucketsUpdateProjection Source # 
Eq BucketsUpdateProjection Source # 
Data BucketsUpdateProjection Source # 

Methods

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

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

toConstr :: BucketsUpdateProjection -> Constr #

dataTypeOf :: BucketsUpdateProjection -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord BucketsUpdateProjection Source # 
Read BucketsUpdateProjection Source # 
Show BucketsUpdateProjection Source # 
Generic BucketsUpdateProjection Source # 
Hashable BucketsUpdateProjection Source # 
ToJSON BucketsUpdateProjection Source # 
FromJSON BucketsUpdateProjection Source # 
FromHttpApiData BucketsUpdateProjection Source # 
ToHttpApiData BucketsUpdateProjection Source # 
type Rep BucketsUpdateProjection Source # 
type Rep BucketsUpdateProjection = D1 (MetaData "BucketsUpdateProjection" "Network.Google.Storage.Types.Sum" "gogol-storage-0.3.0-DGwRnfj7WmaH5CaBqC8AR9" False) ((:+:) (C1 (MetaCons "BUPFull" PrefixI False) U1) (C1 (MetaCons "BUPNoACL" PrefixI False) U1))

ComposeRequest

data ComposeRequest Source #

A Compose request.

See: composeRequest smart constructor.

Instances

Eq ComposeRequest Source # 
Data ComposeRequest Source # 

Methods

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

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

toConstr :: ComposeRequest -> Constr #

dataTypeOf :: ComposeRequest -> DataType #

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

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

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

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

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

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

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

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

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

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

Show ComposeRequest Source # 
Generic ComposeRequest Source # 

Associated Types

type Rep ComposeRequest :: * -> * #

ToJSON ComposeRequest Source # 
FromJSON ComposeRequest Source # 
type Rep ComposeRequest Source # 
type Rep ComposeRequest = D1 (MetaData "ComposeRequest" "Network.Google.Storage.Types.Product" "gogol-storage-0.3.0-DGwRnfj7WmaH5CaBqC8AR9" False) (C1 (MetaCons "ComposeRequest'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_crDestination") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Object))) ((:*:) (S1 (MetaSel (Just Symbol "_crKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "_crSourceObjects") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [ComposeRequestSourceObjectsItem]))))))

composeRequest :: ComposeRequest Source #

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

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

crDestination :: Lens' ComposeRequest (Maybe Object) Source #

Properties of the resulting object.

crKind :: Lens' ComposeRequest Text Source #

The kind of item this is.

crSourceObjects :: Lens' ComposeRequest [ComposeRequestSourceObjectsItem] Source #

The list of source objects that will be concatenated into a single object.

ObjectsInsertPredefinedACL

data ObjectsInsertPredefinedACL Source #

Apply a predefined set of access controls to this object.

Constructors

OIPAAuthenticatedRead

authenticatedRead Object owner gets OWNER access, and allAuthenticatedUsers get READER access.

OIPABucketOwnerFullControl

bucketOwnerFullControl Object owner gets OWNER access, and project team owners get OWNER access.

OIPABucketOwnerRead

bucketOwnerRead Object owner gets OWNER access, and project team owners get READER access.

OIPAPrivate

private Object owner gets OWNER access.

OIPAProjectPrivate

projectPrivate Object owner gets OWNER access, and project team members get access according to their roles.

OIPAPublicRead

publicRead Object owner gets OWNER access, and allUsers get READER access.

Instances

Enum ObjectsInsertPredefinedACL Source # 
Eq ObjectsInsertPredefinedACL Source # 
Data ObjectsInsertPredefinedACL Source # 

Methods

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

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

toConstr :: ObjectsInsertPredefinedACL -> Constr #

dataTypeOf :: ObjectsInsertPredefinedACL -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ObjectsInsertPredefinedACL Source # 
Read ObjectsInsertPredefinedACL Source # 
Show ObjectsInsertPredefinedACL Source # 
Generic ObjectsInsertPredefinedACL Source # 
Hashable ObjectsInsertPredefinedACL Source # 
ToJSON ObjectsInsertPredefinedACL Source # 
FromJSON ObjectsInsertPredefinedACL Source # 
FromHttpApiData ObjectsInsertPredefinedACL Source # 
ToHttpApiData ObjectsInsertPredefinedACL Source # 
type Rep ObjectsInsertPredefinedACL Source # 
type Rep ObjectsInsertPredefinedACL = D1 (MetaData "ObjectsInsertPredefinedACL" "Network.Google.Storage.Types.Sum" "gogol-storage-0.3.0-DGwRnfj7WmaH5CaBqC8AR9" False) ((:+:) ((:+:) (C1 (MetaCons "OIPAAuthenticatedRead" PrefixI False) U1) ((:+:) (C1 (MetaCons "OIPABucketOwnerFullControl" PrefixI False) U1) (C1 (MetaCons "OIPABucketOwnerRead" PrefixI False) U1))) ((:+:) (C1 (MetaCons "OIPAPrivate" PrefixI False) U1) ((:+:) (C1 (MetaCons "OIPAProjectPrivate" PrefixI False) U1) (C1 (MetaCons "OIPAPublicRead" PrefixI False) U1))))

ObjectsListProjection

data ObjectsListProjection Source #

Set of properties to return. Defaults to noAcl.

Constructors

OLPFull

full Include all properties.

OLPNoACL

noAcl Omit the owner, acl property.

Instances

Enum ObjectsListProjection Source # 
Eq ObjectsListProjection Source # 
Data ObjectsListProjection Source # 

Methods

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

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

toConstr :: ObjectsListProjection -> Constr #

dataTypeOf :: ObjectsListProjection -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ObjectsListProjection Source # 
Read ObjectsListProjection Source # 
Show ObjectsListProjection Source # 
Generic ObjectsListProjection Source # 
Hashable ObjectsListProjection Source # 
ToJSON ObjectsListProjection Source # 
FromJSON ObjectsListProjection Source # 
FromHttpApiData ObjectsListProjection Source # 
ToHttpApiData ObjectsListProjection Source # 
type Rep ObjectsListProjection Source # 
type Rep ObjectsListProjection = D1 (MetaData "ObjectsListProjection" "Network.Google.Storage.Types.Sum" "gogol-storage-0.3.0-DGwRnfj7WmaH5CaBqC8AR9" False) ((:+:) (C1 (MetaCons "OLPFull" PrefixI False) U1) (C1 (MetaCons "OLPNoACL" PrefixI False) U1))

BucketsInsertPredefinedDefaultObjectACL

data BucketsInsertPredefinedDefaultObjectACL Source #

Apply a predefined set of default object access controls to this bucket.

Constructors

BIPDOAAuthenticatedRead

authenticatedRead Object owner gets OWNER access, and allAuthenticatedUsers get READER access.

BIPDOABucketOwnerFullControl

bucketOwnerFullControl Object owner gets OWNER access, and project team owners get OWNER access.

BIPDOABucketOwnerRead

bucketOwnerRead Object owner gets OWNER access, and project team owners get READER access.

BIPDOAPrivate

private Object owner gets OWNER access.

BIPDOAProjectPrivate

projectPrivate Object owner gets OWNER access, and project team members get access according to their roles.

BIPDOAPublicRead

publicRead Object owner gets OWNER access, and allUsers get READER access.

Instances

Enum BucketsInsertPredefinedDefaultObjectACL Source # 
Eq BucketsInsertPredefinedDefaultObjectACL Source # 
Data BucketsInsertPredefinedDefaultObjectACL Source # 

Methods

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

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

toConstr :: BucketsInsertPredefinedDefaultObjectACL -> Constr #

dataTypeOf :: BucketsInsertPredefinedDefaultObjectACL -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord BucketsInsertPredefinedDefaultObjectACL Source # 
Read BucketsInsertPredefinedDefaultObjectACL Source # 
Show BucketsInsertPredefinedDefaultObjectACL Source # 
Generic BucketsInsertPredefinedDefaultObjectACL Source # 
Hashable BucketsInsertPredefinedDefaultObjectACL Source # 
ToJSON BucketsInsertPredefinedDefaultObjectACL Source # 
FromJSON BucketsInsertPredefinedDefaultObjectACL Source # 
FromHttpApiData BucketsInsertPredefinedDefaultObjectACL Source # 
ToHttpApiData BucketsInsertPredefinedDefaultObjectACL Source # 
type Rep BucketsInsertPredefinedDefaultObjectACL Source # 
type Rep BucketsInsertPredefinedDefaultObjectACL = D1 (MetaData "BucketsInsertPredefinedDefaultObjectACL" "Network.Google.Storage.Types.Sum" "gogol-storage-0.3.0-DGwRnfj7WmaH5CaBqC8AR9" False) ((:+:) ((:+:) (C1 (MetaCons "BIPDOAAuthenticatedRead" PrefixI False) U1) ((:+:) (C1 (MetaCons "BIPDOABucketOwnerFullControl" PrefixI False) U1) (C1 (MetaCons "BIPDOABucketOwnerRead" PrefixI False) U1))) ((:+:) (C1 (MetaCons "BIPDOAPrivate" PrefixI False) U1) ((:+:) (C1 (MetaCons "BIPDOAProjectPrivate" PrefixI False) U1) (C1 (MetaCons "BIPDOAPublicRead" PrefixI False) U1))))

BucketsUpdatePredefinedACL

data BucketsUpdatePredefinedACL Source #

Apply a predefined set of access controls to this bucket.

Constructors

BUPAAuthenticatedRead

authenticatedRead Project team owners get OWNER access, and allAuthenticatedUsers get READER access.

BUPAPrivate

private Project team owners get OWNER access.

BUPAProjectPrivate

projectPrivate Project team members get access according to their roles.

BUPAPublicRead

publicRead Project team owners get OWNER access, and allUsers get READER access.

BUPAPublicReadWrite

publicReadWrite Project team owners get OWNER access, and allUsers get WRITER access.

Instances

Enum BucketsUpdatePredefinedACL Source # 
Eq BucketsUpdatePredefinedACL Source # 
Data BucketsUpdatePredefinedACL Source # 

Methods

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

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

toConstr :: BucketsUpdatePredefinedACL -> Constr #

dataTypeOf :: BucketsUpdatePredefinedACL -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord BucketsUpdatePredefinedACL Source # 
Read BucketsUpdatePredefinedACL Source # 
Show BucketsUpdatePredefinedACL Source # 
Generic BucketsUpdatePredefinedACL Source # 
Hashable BucketsUpdatePredefinedACL Source # 
ToJSON BucketsUpdatePredefinedACL Source # 
FromJSON BucketsUpdatePredefinedACL Source # 
FromHttpApiData BucketsUpdatePredefinedACL Source # 
ToHttpApiData BucketsUpdatePredefinedACL Source # 
type Rep BucketsUpdatePredefinedACL Source # 
type Rep BucketsUpdatePredefinedACL = D1 (MetaData "BucketsUpdatePredefinedACL" "Network.Google.Storage.Types.Sum" "gogol-storage-0.3.0-DGwRnfj7WmaH5CaBqC8AR9" False) ((:+:) ((:+:) (C1 (MetaCons "BUPAAuthenticatedRead" PrefixI False) U1) (C1 (MetaCons "BUPAPrivate" PrefixI False) U1)) ((:+:) (C1 (MetaCons "BUPAProjectPrivate" PrefixI False) U1) ((:+:) (C1 (MetaCons "BUPAPublicRead" PrefixI False) U1) (C1 (MetaCons "BUPAPublicReadWrite" PrefixI False) U1))))

ObjectsCopyDestinationPredefinedACL

data ObjectsCopyDestinationPredefinedACL Source #

Apply a predefined set of access controls to the destination object.

Constructors

OCDPACLAuthenticatedRead

authenticatedRead Object owner gets OWNER access, and allAuthenticatedUsers get READER access.

OCDPACLBucketOwnerFullControl

bucketOwnerFullControl Object owner gets OWNER access, and project team owners get OWNER access.

OCDPACLBucketOwnerRead

bucketOwnerRead Object owner gets OWNER access, and project team owners get READER access.

OCDPACLPrivate

private Object owner gets OWNER access.

OCDPACLProjectPrivate

projectPrivate Object owner gets OWNER access, and project team members get access according to their roles.

OCDPACLPublicRead

publicRead Object owner gets OWNER access, and allUsers get READER access.

Instances

Enum ObjectsCopyDestinationPredefinedACL Source # 
Eq ObjectsCopyDestinationPredefinedACL Source # 
Data ObjectsCopyDestinationPredefinedACL Source # 

Methods

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

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

toConstr :: ObjectsCopyDestinationPredefinedACL -> Constr #

dataTypeOf :: ObjectsCopyDestinationPredefinedACL -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ObjectsCopyDestinationPredefinedACL Source # 
Read ObjectsCopyDestinationPredefinedACL Source # 
Show ObjectsCopyDestinationPredefinedACL Source # 
Generic ObjectsCopyDestinationPredefinedACL Source # 
Hashable ObjectsCopyDestinationPredefinedACL Source # 
ToJSON ObjectsCopyDestinationPredefinedACL Source # 
FromJSON ObjectsCopyDestinationPredefinedACL Source # 
FromHttpApiData ObjectsCopyDestinationPredefinedACL Source # 
ToHttpApiData ObjectsCopyDestinationPredefinedACL Source # 
type Rep ObjectsCopyDestinationPredefinedACL Source # 
type Rep ObjectsCopyDestinationPredefinedACL = D1 (MetaData "ObjectsCopyDestinationPredefinedACL" "Network.Google.Storage.Types.Sum" "gogol-storage-0.3.0-DGwRnfj7WmaH5CaBqC8AR9" False) ((:+:) ((:+:) (C1 (MetaCons "OCDPACLAuthenticatedRead" PrefixI False) U1) ((:+:) (C1 (MetaCons "OCDPACLBucketOwnerFullControl" PrefixI False) U1) (C1 (MetaCons "OCDPACLBucketOwnerRead" PrefixI False) U1))) ((:+:) (C1 (MetaCons "OCDPACLPrivate" PrefixI False) U1) ((:+:) (C1 (MetaCons "OCDPACLProjectPrivate" PrefixI False) U1) (C1 (MetaCons "OCDPACLPublicRead" PrefixI False) U1))))

ObjectsUpdatePredefinedACL

data ObjectsUpdatePredefinedACL Source #

Apply a predefined set of access controls to this object.

Constructors

OUPAAuthenticatedRead

authenticatedRead Object owner gets OWNER access, and allAuthenticatedUsers get READER access.

OUPABucketOwnerFullControl

bucketOwnerFullControl Object owner gets OWNER access, and project team owners get OWNER access.

OUPABucketOwnerRead

bucketOwnerRead Object owner gets OWNER access, and project team owners get READER access.

OUPAPrivate

private Object owner gets OWNER access.

OUPAProjectPrivate

projectPrivate Object owner gets OWNER access, and project team members get access according to their roles.

OUPAPublicRead

publicRead Object owner gets OWNER access, and allUsers get READER access.

Instances

Enum ObjectsUpdatePredefinedACL Source # 
Eq ObjectsUpdatePredefinedACL Source # 
Data ObjectsUpdatePredefinedACL Source # 

Methods

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

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

toConstr :: ObjectsUpdatePredefinedACL -> Constr #

dataTypeOf :: ObjectsUpdatePredefinedACL -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ObjectsUpdatePredefinedACL Source # 
Read ObjectsUpdatePredefinedACL Source # 
Show ObjectsUpdatePredefinedACL Source # 
Generic ObjectsUpdatePredefinedACL Source # 
Hashable ObjectsUpdatePredefinedACL Source # 
ToJSON ObjectsUpdatePredefinedACL Source # 
FromJSON ObjectsUpdatePredefinedACL Source # 
FromHttpApiData ObjectsUpdatePredefinedACL Source # 
ToHttpApiData ObjectsUpdatePredefinedACL Source # 
type Rep ObjectsUpdatePredefinedACL Source # 
type Rep ObjectsUpdatePredefinedACL = D1 (MetaData "ObjectsUpdatePredefinedACL" "Network.Google.Storage.Types.Sum" "gogol-storage-0.3.0-DGwRnfj7WmaH5CaBqC8AR9" False) ((:+:) ((:+:) (C1 (MetaCons "OUPAAuthenticatedRead" PrefixI False) U1) ((:+:) (C1 (MetaCons "OUPABucketOwnerFullControl" PrefixI False) U1) (C1 (MetaCons "OUPABucketOwnerRead" PrefixI False) U1))) ((:+:) (C1 (MetaCons "OUPAPrivate" PrefixI False) U1) ((:+:) (C1 (MetaCons "OUPAProjectPrivate" PrefixI False) U1) (C1 (MetaCons "OUPAPublicRead" PrefixI False) U1))))

BucketOwner

data BucketOwner Source #

The owner of the bucket. This is always the project team's owner group.

See: bucketOwner smart constructor.

Instances

Eq BucketOwner Source # 
Data BucketOwner Source # 

Methods

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

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

toConstr :: BucketOwner -> Constr #

dataTypeOf :: BucketOwner -> DataType #

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

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

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

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

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

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

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

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

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

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

Show BucketOwner Source # 
Generic BucketOwner Source # 

Associated Types

type Rep BucketOwner :: * -> * #

ToJSON BucketOwner Source # 
FromJSON BucketOwner Source # 
type Rep BucketOwner Source # 
type Rep BucketOwner = D1 (MetaData "BucketOwner" "Network.Google.Storage.Types.Product" "gogol-storage-0.3.0-DGwRnfj7WmaH5CaBqC8AR9" False) (C1 (MetaCons "BucketOwner'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_boEntity") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_boEntityId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))

bucketOwner :: BucketOwner Source #

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

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

boEntity :: Lens' BucketOwner (Maybe Text) Source #

The entity, in the form project-owner-projectId.

boEntityId :: Lens' BucketOwner (Maybe Text) Source #

The ID for the entity.

ComposeRequestSourceObjectsItem

data ComposeRequestSourceObjectsItem Source #

Instances

Eq ComposeRequestSourceObjectsItem Source # 
Data ComposeRequestSourceObjectsItem Source # 

Methods

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

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

toConstr :: ComposeRequestSourceObjectsItem -> Constr #

dataTypeOf :: ComposeRequestSourceObjectsItem -> DataType #

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

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

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

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

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

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

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

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

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

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

Show ComposeRequestSourceObjectsItem Source # 
Generic ComposeRequestSourceObjectsItem Source # 
ToJSON ComposeRequestSourceObjectsItem Source # 
FromJSON ComposeRequestSourceObjectsItem Source # 
type Rep ComposeRequestSourceObjectsItem Source # 
type Rep ComposeRequestSourceObjectsItem = D1 (MetaData "ComposeRequestSourceObjectsItem" "Network.Google.Storage.Types.Product" "gogol-storage-0.3.0-DGwRnfj7WmaH5CaBqC8AR9" False) (C1 (MetaCons "ComposeRequestSourceObjectsItem'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_crsoiName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_crsoiObjectPreconditions") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ComposeRequestSourceObjectsItemObjectPreconditions))) (S1 (MetaSel (Just Symbol "_crsoiGeneration") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))))))

composeRequestSourceObjectsItem :: ComposeRequestSourceObjectsItem Source #

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

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

crsoiName :: Lens' ComposeRequestSourceObjectsItem (Maybe Text) Source #

The source object's name. The source object's bucket is implicitly the destination bucket.

crsoiGeneration :: Lens' ComposeRequestSourceObjectsItem (Maybe Int64) Source #

The generation of this object to use as the source.

BucketsInsertProjection

data BucketsInsertProjection Source #

Set of properties to return. Defaults to noAcl, unless the bucket resource specifies acl or defaultObjectAcl properties, when it defaults to full.

Constructors

BIPFull

full Include all properties.

BIPNoACL

noAcl Omit owner, acl and defaultObjectAcl properties.

Instances

Enum BucketsInsertProjection Source # 
Eq BucketsInsertProjection Source # 
Data BucketsInsertProjection Source # 

Methods

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

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

toConstr :: BucketsInsertProjection -> Constr #

dataTypeOf :: BucketsInsertProjection -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord BucketsInsertProjection Source # 
Read BucketsInsertProjection Source # 
Show BucketsInsertProjection Source # 
Generic BucketsInsertProjection Source # 
Hashable BucketsInsertProjection Source # 
ToJSON BucketsInsertProjection Source # 
FromJSON BucketsInsertProjection Source # 
FromHttpApiData BucketsInsertProjection Source # 
ToHttpApiData BucketsInsertProjection Source # 
type Rep BucketsInsertProjection Source # 
type Rep BucketsInsertProjection = D1 (MetaData "BucketsInsertProjection" "Network.Google.Storage.Types.Sum" "gogol-storage-0.3.0-DGwRnfj7WmaH5CaBqC8AR9" False) ((:+:) (C1 (MetaCons "BIPFull" PrefixI False) U1) (C1 (MetaCons "BIPNoACL" PrefixI False) U1))

ChannelParams

data ChannelParams Source #

Additional parameters controlling delivery channel behavior. Optional.

See: channelParams smart constructor.

Instances

Eq ChannelParams Source # 
Data ChannelParams Source # 

Methods

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

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

toConstr :: ChannelParams -> Constr #

dataTypeOf :: ChannelParams -> DataType #

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

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

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

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

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

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

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

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

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

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

Show ChannelParams Source # 
Generic ChannelParams Source # 

Associated Types

type Rep ChannelParams :: * -> * #

ToJSON ChannelParams Source # 
FromJSON ChannelParams Source # 
type Rep ChannelParams Source # 
type Rep ChannelParams = D1 (MetaData "ChannelParams" "Network.Google.Storage.Types.Product" "gogol-storage-0.3.0-DGwRnfj7WmaH5CaBqC8AR9" True) (C1 (MetaCons "ChannelParams'" PrefixI True) (S1 (MetaSel (Just Symbol "_cpAddtional") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (HashMap Text Text))))

channelParams Source #

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

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

cpAddtional :: Lens' ChannelParams (HashMap Text Text) Source #

Declares a new parameter by name.

BucketsListProjection

data BucketsListProjection Source #

Set of properties to return. Defaults to noAcl.

Constructors

BLPFull

full Include all properties.

BLPNoACL

noAcl Omit owner, acl and defaultObjectAcl properties.

Instances

Enum BucketsListProjection Source # 
Eq BucketsListProjection Source # 
Data BucketsListProjection Source # 

Methods

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

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

toConstr :: BucketsListProjection -> Constr #

dataTypeOf :: BucketsListProjection -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord BucketsListProjection Source # 
Read BucketsListProjection Source # 
Show BucketsListProjection Source # 
Generic BucketsListProjection Source # 
Hashable BucketsListProjection Source # 
ToJSON BucketsListProjection Source # 
FromJSON BucketsListProjection Source # 
FromHttpApiData BucketsListProjection Source # 
ToHttpApiData BucketsListProjection Source # 
type Rep BucketsListProjection Source # 
type Rep BucketsListProjection = D1 (MetaData "BucketsListProjection" "Network.Google.Storage.Types.Sum" "gogol-storage-0.3.0-DGwRnfj7WmaH5CaBqC8AR9" False) ((:+:) (C1 (MetaCons "BLPFull" PrefixI False) U1) (C1 (MetaCons "BLPNoACL" PrefixI False) U1))

ObjectsUpdateProjection

data ObjectsUpdateProjection Source #

Set of properties to return. Defaults to full.

Constructors

OUPFull

full Include all properties.

OUPNoACL

noAcl Omit the owner, acl property.

Instances

Enum ObjectsUpdateProjection Source # 
Eq ObjectsUpdateProjection Source # 
Data ObjectsUpdateProjection Source # 

Methods

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

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

toConstr :: ObjectsUpdateProjection -> Constr #

dataTypeOf :: ObjectsUpdateProjection -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ObjectsUpdateProjection Source # 
Read ObjectsUpdateProjection Source # 
Show ObjectsUpdateProjection Source # 
Generic ObjectsUpdateProjection Source # 
Hashable ObjectsUpdateProjection Source # 
ToJSON ObjectsUpdateProjection Source # 
FromJSON ObjectsUpdateProjection Source # 
FromHttpApiData ObjectsUpdateProjection Source # 
ToHttpApiData ObjectsUpdateProjection Source # 
type Rep ObjectsUpdateProjection Source # 
type Rep ObjectsUpdateProjection = D1 (MetaData "ObjectsUpdateProjection" "Network.Google.Storage.Types.Sum" "gogol-storage-0.3.0-DGwRnfj7WmaH5CaBqC8AR9" False) ((:+:) (C1 (MetaCons "OUPFull" PrefixI False) U1) (C1 (MetaCons "OUPNoACL" PrefixI False) U1))

Object

data Object Source #

An object.

See: object' smart constructor.

Instances

Eq Object Source # 

Methods

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

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

Data Object Source # 

Methods

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

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

toConstr :: Object -> Constr #

dataTypeOf :: Object -> DataType #

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

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

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

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

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

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

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

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

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

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

Show Object Source # 
Generic Object Source # 

Associated Types

type Rep Object :: * -> * #

Methods

from :: Object -> Rep Object x #

to :: Rep Object x -> Object #

ToJSON Object Source # 
FromJSON Object Source # 
type Rep Object Source # 
type Rep Object = D1 (MetaData "Object" "Network.Google.Storage.Types.Product" "gogol-storage-0.3.0-DGwRnfj7WmaH5CaBqC8AR9" False) (C1 (MetaCons "Object'" PrefixI True) ((:*:) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_objEtag") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_objTimeStorageClassUpdated") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DateTime'))) (S1 (MetaSel (Just Symbol "_objSize") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Word64)))))) ((:*:) (S1 (MetaSel (Just Symbol "_objKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) ((:*:) (S1 (MetaSel (Just Symbol "_objTimeDeleted") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DateTime'))) (S1 (MetaSel (Just Symbol "_objCrc32c") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_objCustomerEncryption") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ObjectCustomerEncryption))) ((:*:) (S1 (MetaSel (Just Symbol "_objBucket") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_objOwner") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ObjectOwner))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_objSelfLink") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_objMediaLink") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_objComponentCount") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32)))) (S1 (MetaSel (Just Symbol "_objName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))))) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_objStorageClass") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_objContentEncoding") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_objMetadata") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ObjectMetadata))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_objTimeCreated") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DateTime'))) (S1 (MetaSel (Just Symbol "_objId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_objUpdated") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DateTime'))) (S1 (MetaSel (Just Symbol "_objContentLanguage") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_objCacheControl") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_objMetageneration") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) (S1 (MetaSel (Just Symbol "_objGeneration") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_objACL") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [ObjectAccessControl]))) (S1 (MetaSel (Just Symbol "_objContentDisPosition") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_objMD5Hash") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_objContentType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))))))

objEtag :: Lens' Object (Maybe Text) Source #

HTTP 1.1 Entity tag for the object.

objTimeStorageClassUpdated :: Lens' Object (Maybe UTCTime) Source #

The time at which the object's storage class was last changed. When the object is initially created, it will be set to timeCreated.

objSize :: Lens' Object (Maybe Word64) Source #

Content-Length of the data in bytes.

objKind :: Lens' Object Text Source #

The kind of item this is. For objects, this is always storage#object.

objTimeDeleted :: Lens' Object (Maybe UTCTime) Source #

The deletion time of the object in RFC 3339 format. Will be returned if and only if this version of the object has been deleted.

objCrc32c :: Lens' Object (Maybe Text) Source #

CRC32c checksum, as described in RFC 4960, Appendix B; encoded using base64 in big-endian byte order. For more information about using the CRC32c checksum, see Hashes and ETags: Best Practices.

objCustomerEncryption :: Lens' Object (Maybe ObjectCustomerEncryption) Source #

Metadata of customer-supplied encryption key, if the object is encrypted by such a key.

objBucket :: Lens' Object (Maybe Text) Source #

The name of the bucket containing this object.

objOwner :: Lens' Object (Maybe ObjectOwner) Source #

The owner of the object. This will always be the uploader of the object.

objSelfLink :: Lens' Object (Maybe Text) Source #

The link to this object.

objMediaLink :: Lens' Object (Maybe Text) Source #

Media download link.

objComponentCount :: Lens' Object (Maybe Int32) Source #

Number of underlying components that make up this object. Components are accumulated by compose operations.

objName :: Lens' Object (Maybe Text) Source #

The name of this object. Required if not specified by URL parameter.

objStorageClass :: Lens' Object (Maybe Text) Source #

Storage class of the object.

objContentEncoding :: Lens' Object (Maybe Text) Source #

Content-Encoding of the object data.

objMetadata :: Lens' Object (Maybe ObjectMetadata) Source #

User-provided metadata, in key/value pairs.

objTimeCreated :: Lens' Object (Maybe UTCTime) Source #

The creation time of the object in RFC 3339 format.

objId :: Lens' Object (Maybe Text) Source #

The ID of the object.

objUpdated :: Lens' Object (Maybe UTCTime) Source #

The modification time of the object metadata in RFC 3339 format.

objContentLanguage :: Lens' Object (Maybe Text) Source #

Content-Language of the object data.

objCacheControl :: Lens' Object (Maybe Text) Source #

Cache-Control directive for the object data. If omitted, and the object is accessible to all anonymous users, the default will be public, max-age=3600.

objMetageneration :: Lens' Object (Maybe Int64) Source #

The version of the metadata for this object at this generation. Used for preconditions and for detecting changes in metadata. A metageneration number is only meaningful in the context of a particular generation of a particular object.

objGeneration :: Lens' Object (Maybe Int64) Source #

The content generation of this object. Used for object versioning.

objACL :: Lens' Object [ObjectAccessControl] Source #

Access controls on the object.

objContentDisPosition :: Lens' Object (Maybe Text) Source #

Content-Disposition of the object data.

objMD5Hash :: Lens' Object (Maybe Text) Source #

MD5 hash of the data; encoded using base64. For more information about using the MD5 hash, see Hashes and ETags: Best Practices.

objContentType :: Lens' Object (Maybe Text) Source #

Content-Type of the object data. If contentType is not specified, object downloads will be served as application/octet-stream.

ObjectsPatchProjection

data ObjectsPatchProjection Source #

Set of properties to return. Defaults to full.

Constructors

OPPFull

full Include all properties.

OPPNoACL

noAcl Omit the owner, acl property.

Instances

Enum ObjectsPatchProjection Source # 
Eq ObjectsPatchProjection Source # 
Data ObjectsPatchProjection Source # 

Methods

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

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

toConstr :: ObjectsPatchProjection -> Constr #

dataTypeOf :: ObjectsPatchProjection -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ObjectsPatchProjection Source # 
Read ObjectsPatchProjection Source # 
Show ObjectsPatchProjection Source # 
Generic ObjectsPatchProjection Source # 
Hashable ObjectsPatchProjection Source # 
ToJSON ObjectsPatchProjection Source # 
FromJSON ObjectsPatchProjection Source # 
FromHttpApiData ObjectsPatchProjection Source # 
ToHttpApiData ObjectsPatchProjection Source # 
type Rep ObjectsPatchProjection Source # 
type Rep ObjectsPatchProjection = D1 (MetaData "ObjectsPatchProjection" "Network.Google.Storage.Types.Sum" "gogol-storage-0.3.0-DGwRnfj7WmaH5CaBqC8AR9" False) ((:+:) (C1 (MetaCons "OPPFull" PrefixI False) U1) (C1 (MetaCons "OPPNoACL" PrefixI False) U1))

ComposeRequestSourceObjectsItemObjectPreconditions

data ComposeRequestSourceObjectsItemObjectPreconditions Source #

Conditions that must be met for this operation to execute.

See: composeRequestSourceObjectsItemObjectPreconditions smart constructor.

Instances

Eq ComposeRequestSourceObjectsItemObjectPreconditions Source # 
Data ComposeRequestSourceObjectsItemObjectPreconditions Source # 

Methods

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

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

toConstr :: ComposeRequestSourceObjectsItemObjectPreconditions -> Constr #

dataTypeOf :: ComposeRequestSourceObjectsItemObjectPreconditions -> DataType #

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

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

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

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

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

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

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

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

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

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

Show ComposeRequestSourceObjectsItemObjectPreconditions Source # 
Generic ComposeRequestSourceObjectsItemObjectPreconditions Source # 
ToJSON ComposeRequestSourceObjectsItemObjectPreconditions Source # 
FromJSON ComposeRequestSourceObjectsItemObjectPreconditions Source # 
type Rep ComposeRequestSourceObjectsItemObjectPreconditions Source # 
type Rep ComposeRequestSourceObjectsItemObjectPreconditions = D1 (MetaData "ComposeRequestSourceObjectsItemObjectPreconditions" "Network.Google.Storage.Types.Product" "gogol-storage-0.3.0-DGwRnfj7WmaH5CaBqC8AR9" True) (C1 (MetaCons "ComposeRequestSourceObjectsItemObjectPreconditions'" PrefixI True) (S1 (MetaSel (Just Symbol "_crsoiopIfGenerationMatch") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (Textual Int64)))))

composeRequestSourceObjectsItemObjectPreconditions :: ComposeRequestSourceObjectsItemObjectPreconditions Source #

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

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

crsoiopIfGenerationMatch :: Lens' ComposeRequestSourceObjectsItemObjectPreconditions (Maybe Int64) Source #

Only perform the composition if the generation of the source object that would be used matches this value. If this value and a generation are both specified, they must be the same value or the call will fail.

BucketAccessControlProjectTeam

data BucketAccessControlProjectTeam Source #

The project team associated with the entity, if any.

See: bucketAccessControlProjectTeam smart constructor.

Instances

Eq BucketAccessControlProjectTeam Source # 
Data BucketAccessControlProjectTeam Source # 

Methods

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

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

toConstr :: BucketAccessControlProjectTeam -> Constr #

dataTypeOf :: BucketAccessControlProjectTeam -> DataType #

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

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

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

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

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

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

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

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

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

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

Show BucketAccessControlProjectTeam Source # 
Generic BucketAccessControlProjectTeam Source # 
ToJSON BucketAccessControlProjectTeam Source # 
FromJSON BucketAccessControlProjectTeam Source # 
type Rep BucketAccessControlProjectTeam Source # 
type Rep BucketAccessControlProjectTeam = D1 (MetaData "BucketAccessControlProjectTeam" "Network.Google.Storage.Types.Product" "gogol-storage-0.3.0-DGwRnfj7WmaH5CaBqC8AR9" False) (C1 (MetaCons "BucketAccessControlProjectTeam'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_bacptProjectNumber") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_bacptTeam") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))

bucketAccessControlProjectTeam :: BucketAccessControlProjectTeam Source #

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

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

ObjectAccessControls

data ObjectAccessControls Source #

An access-control list.

See: objectAccessControls smart constructor.

Instances

Eq ObjectAccessControls Source # 
Data ObjectAccessControls Source # 

Methods

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

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

toConstr :: ObjectAccessControls -> Constr #

dataTypeOf :: ObjectAccessControls -> DataType #

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

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

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

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

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

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

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

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

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

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

Show ObjectAccessControls Source # 
Generic ObjectAccessControls Source # 
ToJSON ObjectAccessControls Source # 
FromJSON ObjectAccessControls Source # 
type Rep ObjectAccessControls Source # 
type Rep ObjectAccessControls = D1 (MetaData "ObjectAccessControls" "Network.Google.Storage.Types.Product" "gogol-storage-0.3.0-DGwRnfj7WmaH5CaBqC8AR9" False) (C1 (MetaCons "ObjectAccessControls'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_oacKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "_oacItems") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [ObjectAccessControl])))))

objectAccessControls :: ObjectAccessControls Source #

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

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

oacKind :: Lens' ObjectAccessControls Text Source #

The kind of item this is. For lists of object access control entries, this is always storage#objectAccessControls.

BucketWebsite

data BucketWebsite Source #

The bucket's website configuration, controlling how the service behaves when accessing bucket contents as a web site. See the Static Website Examples for more information.

See: bucketWebsite smart constructor.

Instances

Eq BucketWebsite Source # 
Data BucketWebsite Source # 

Methods

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

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

toConstr :: BucketWebsite -> Constr #

dataTypeOf :: BucketWebsite -> DataType #

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

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

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

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

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

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

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

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

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

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

Show BucketWebsite Source # 
Generic BucketWebsite Source # 

Associated Types

type Rep BucketWebsite :: * -> * #

ToJSON BucketWebsite Source # 
FromJSON BucketWebsite Source # 
type Rep BucketWebsite Source # 
type Rep BucketWebsite = D1 (MetaData "BucketWebsite" "Network.Google.Storage.Types.Product" "gogol-storage-0.3.0-DGwRnfj7WmaH5CaBqC8AR9" False) (C1 (MetaCons "BucketWebsite'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_bwMainPageSuffix") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_bwNotFoundPage") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))

bucketWebsite :: BucketWebsite Source #

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

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

bwMainPageSuffix :: Lens' BucketWebsite (Maybe Text) Source #

If the requested object path is missing, the service will ensure the path has a trailing '/', append this suffix, and attempt to retrieve the resulting object. This allows the creation of index.html objects to represent directory pages.

bwNotFoundPage :: Lens' BucketWebsite (Maybe Text) Source #

If the requested object path is missing, and any mainPageSuffix object is missing, if applicable, the service will return the named object from this bucket as the content for a 404 Not Found result.

BucketAccessControl

data BucketAccessControl Source #

An access-control entry.

See: bucketAccessControl smart constructor.

Instances

Eq BucketAccessControl Source # 
Data BucketAccessControl Source # 

Methods

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

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

toConstr :: BucketAccessControl -> Constr #

dataTypeOf :: BucketAccessControl -> DataType #

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

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

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

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

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

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

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

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

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

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

Show BucketAccessControl Source # 
Generic BucketAccessControl Source # 
ToJSON BucketAccessControl Source # 
FromJSON BucketAccessControl Source # 
type Rep BucketAccessControl Source # 
type Rep BucketAccessControl = D1 (MetaData "BucketAccessControl" "Network.Google.Storage.Types.Product" "gogol-storage-0.3.0-DGwRnfj7WmaH5CaBqC8AR9" False) (C1 (MetaCons "BucketAccessControl'" PrefixI True) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_bacaEmail") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_bacaEtag") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_bacaKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) ((:*:) (S1 (MetaSel (Just Symbol "_bacaDomain") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_bacaBucket") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_bacaRole") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_bacaSelfLink") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_bacaId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))) ((:*:) (S1 (MetaSel (Just Symbol "_bacaProjectTeam") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe BucketAccessControlProjectTeam))) ((:*:) (S1 (MetaSel (Just Symbol "_bacaEntity") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_bacaEntityId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))))))

bucketAccessControl :: BucketAccessControl Source #

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

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

bacaEmail :: Lens' BucketAccessControl (Maybe Text) Source #

The email address associated with the entity, if any.

bacaEtag :: Lens' BucketAccessControl (Maybe Text) Source #

HTTP 1.1 Entity tag for the access-control entry.

bacaKind :: Lens' BucketAccessControl Text Source #

The kind of item this is. For bucket access control entries, this is always storage#bucketAccessControl.

bacaDomain :: Lens' BucketAccessControl (Maybe Text) Source #

The domain associated with the entity, if any.

bacaBucket :: Lens' BucketAccessControl (Maybe Text) Source #

The name of the bucket.

bacaRole :: Lens' BucketAccessControl (Maybe Text) Source #

The access permission for the entity.

bacaSelfLink :: Lens' BucketAccessControl (Maybe Text) Source #

The link to this access-control entry.

bacaId :: Lens' BucketAccessControl (Maybe Text) Source #

The ID of the access-control entry.

bacaProjectTeam :: Lens' BucketAccessControl (Maybe BucketAccessControlProjectTeam) Source #

The project team associated with the entity, if any.

bacaEntity :: Lens' BucketAccessControl (Maybe Text) Source #

The entity holding the permission, in one of the following forms: - user-userId - user-email - group-groupId - group-email - domain-domain - project-team-projectId - allUsers - allAuthenticatedUsers Examples: - The user liz'example.com would be user-liz'example.com. - The group example'googlegroups.com would be group-example'googlegroups.com. - To refer to all members of the Google Apps for Business domain example.com, the entity would be domain-example.com.

bacaEntityId :: Lens' BucketAccessControl (Maybe Text) Source #

The ID for the entity, if any.

BucketLifecycleRuleItemAction

data BucketLifecycleRuleItemAction Source #

The action to take.

See: bucketLifecycleRuleItemAction smart constructor.

Instances

Eq BucketLifecycleRuleItemAction Source # 
Data BucketLifecycleRuleItemAction Source # 

Methods

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

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

toConstr :: BucketLifecycleRuleItemAction -> Constr #

dataTypeOf :: BucketLifecycleRuleItemAction -> DataType #

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

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

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

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

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

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

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

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

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

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

Show BucketLifecycleRuleItemAction Source # 
Generic BucketLifecycleRuleItemAction Source # 
ToJSON BucketLifecycleRuleItemAction Source # 
FromJSON BucketLifecycleRuleItemAction Source # 
type Rep BucketLifecycleRuleItemAction Source # 
type Rep BucketLifecycleRuleItemAction = D1 (MetaData "BucketLifecycleRuleItemAction" "Network.Google.Storage.Types.Product" "gogol-storage-0.3.0-DGwRnfj7WmaH5CaBqC8AR9" False) (C1 (MetaCons "BucketLifecycleRuleItemAction'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_blriaStorageClass") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_blriaType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))

bucketLifecycleRuleItemAction :: BucketLifecycleRuleItemAction Source #

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

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

blriaStorageClass :: Lens' BucketLifecycleRuleItemAction (Maybe Text) Source #

Target storage class. Required iff the type of the action is SetStorageClass.

blriaType :: Lens' BucketLifecycleRuleItemAction (Maybe Text) Source #

Type of the action. Currently, only Delete and SetStorageClass are supported.

ObjectsGetProjection

data ObjectsGetProjection Source #

Set of properties to return. Defaults to noAcl.

Constructors

OGPFull

full Include all properties.

OGPNoACL

noAcl Omit the owner, acl property.

Instances

Enum ObjectsGetProjection Source # 
Eq ObjectsGetProjection Source # 
Data ObjectsGetProjection Source # 

Methods

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

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

toConstr :: ObjectsGetProjection -> Constr #

dataTypeOf :: ObjectsGetProjection -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ObjectsGetProjection Source # 
Read ObjectsGetProjection Source # 
Show ObjectsGetProjection Source # 
Generic ObjectsGetProjection Source # 
Hashable ObjectsGetProjection Source # 
ToJSON ObjectsGetProjection Source # 
FromJSON ObjectsGetProjection Source # 
FromHttpApiData ObjectsGetProjection Source # 
ToHttpApiData ObjectsGetProjection Source # 
type Rep ObjectsGetProjection Source # 
type Rep ObjectsGetProjection = D1 (MetaData "ObjectsGetProjection" "Network.Google.Storage.Types.Sum" "gogol-storage-0.3.0-DGwRnfj7WmaH5CaBqC8AR9" False) ((:+:) (C1 (MetaCons "OGPFull" PrefixI False) U1) (C1 (MetaCons "OGPNoACL" PrefixI False) U1))

BucketsPatchPredefinedDefaultObjectACL

data BucketsPatchPredefinedDefaultObjectACL Source #

Apply a predefined set of default object access controls to this bucket.

Constructors

BPPDOAAuthenticatedRead

authenticatedRead Object owner gets OWNER access, and allAuthenticatedUsers get READER access.

BPPDOABucketOwnerFullControl

bucketOwnerFullControl Object owner gets OWNER access, and project team owners get OWNER access.

BPPDOABucketOwnerRead

bucketOwnerRead Object owner gets OWNER access, and project team owners get READER access.

BPPDOAPrivate

private Object owner gets OWNER access.

BPPDOAProjectPrivate

projectPrivate Object owner gets OWNER access, and project team members get access according to their roles.

BPPDOAPublicRead

publicRead Object owner gets OWNER access, and allUsers get READER access.

Instances

Enum BucketsPatchPredefinedDefaultObjectACL Source # 
Eq BucketsPatchPredefinedDefaultObjectACL Source # 
Data BucketsPatchPredefinedDefaultObjectACL Source # 

Methods

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

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

toConstr :: BucketsPatchPredefinedDefaultObjectACL -> Constr #

dataTypeOf :: BucketsPatchPredefinedDefaultObjectACL -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord BucketsPatchPredefinedDefaultObjectACL Source # 
Read BucketsPatchPredefinedDefaultObjectACL Source # 
Show BucketsPatchPredefinedDefaultObjectACL Source # 
Generic BucketsPatchPredefinedDefaultObjectACL Source # 
Hashable BucketsPatchPredefinedDefaultObjectACL Source # 
ToJSON BucketsPatchPredefinedDefaultObjectACL Source # 
FromJSON BucketsPatchPredefinedDefaultObjectACL Source # 
FromHttpApiData BucketsPatchPredefinedDefaultObjectACL Source # 
ToHttpApiData BucketsPatchPredefinedDefaultObjectACL Source # 
type Rep BucketsPatchPredefinedDefaultObjectACL Source # 
type Rep BucketsPatchPredefinedDefaultObjectACL = D1 (MetaData "BucketsPatchPredefinedDefaultObjectACL" "Network.Google.Storage.Types.Sum" "gogol-storage-0.3.0-DGwRnfj7WmaH5CaBqC8AR9" False) ((:+:) ((:+:) (C1 (MetaCons "BPPDOAAuthenticatedRead" PrefixI False) U1) ((:+:) (C1 (MetaCons "BPPDOABucketOwnerFullControl" PrefixI False) U1) (C1 (MetaCons "BPPDOABucketOwnerRead" PrefixI False) U1))) ((:+:) (C1 (MetaCons "BPPDOAPrivate" PrefixI False) U1) ((:+:) (C1 (MetaCons "BPPDOAProjectPrivate" PrefixI False) U1) (C1 (MetaCons "BPPDOAPublicRead" PrefixI False) U1))))

BucketsPatchPredefinedACL

data BucketsPatchPredefinedACL Source #

Apply a predefined set of access controls to this bucket.

Constructors

BPPAAuthenticatedRead

authenticatedRead Project team owners get OWNER access, and allAuthenticatedUsers get READER access.

BPPAPrivate

private Project team owners get OWNER access.

BPPAProjectPrivate

projectPrivate Project team members get access according to their roles.

BPPAPublicRead

publicRead Project team owners get OWNER access, and allUsers get READER access.

BPPAPublicReadWrite

publicReadWrite Project team owners get OWNER access, and allUsers get WRITER access.

Instances

Enum BucketsPatchPredefinedACL Source # 
Eq BucketsPatchPredefinedACL Source # 
Data BucketsPatchPredefinedACL Source # 

Methods

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

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

toConstr :: BucketsPatchPredefinedACL -> Constr #

dataTypeOf :: BucketsPatchPredefinedACL -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord BucketsPatchPredefinedACL Source # 
Read BucketsPatchPredefinedACL Source # 
Show BucketsPatchPredefinedACL Source # 
Generic BucketsPatchPredefinedACL Source # 
Hashable BucketsPatchPredefinedACL Source # 
ToJSON BucketsPatchPredefinedACL Source # 
FromJSON BucketsPatchPredefinedACL Source # 
FromHttpApiData BucketsPatchPredefinedACL Source # 
ToHttpApiData BucketsPatchPredefinedACL Source # 
type Rep BucketsPatchPredefinedACL Source # 
type Rep BucketsPatchPredefinedACL = D1 (MetaData "BucketsPatchPredefinedACL" "Network.Google.Storage.Types.Sum" "gogol-storage-0.3.0-DGwRnfj7WmaH5CaBqC8AR9" False) ((:+:) ((:+:) (C1 (MetaCons "BPPAAuthenticatedRead" PrefixI False) U1) (C1 (MetaCons "BPPAPrivate" PrefixI False) U1)) ((:+:) (C1 (MetaCons "BPPAProjectPrivate" PrefixI False) U1) ((:+:) (C1 (MetaCons "BPPAPublicRead" PrefixI False) U1) (C1 (MetaCons "BPPAPublicReadWrite" PrefixI False) U1))))

ObjectAccessControl

data ObjectAccessControl Source #

An access-control entry.

See: objectAccessControl smart constructor.

Instances

Eq ObjectAccessControl Source # 
Data ObjectAccessControl Source # 

Methods

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

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

toConstr :: ObjectAccessControl -> Constr #

dataTypeOf :: ObjectAccessControl -> DataType #

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

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

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

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

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

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

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

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

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

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

Show ObjectAccessControl Source # 
Generic ObjectAccessControl Source # 
ToJSON ObjectAccessControl Source # 
FromJSON ObjectAccessControl Source # 
type Rep ObjectAccessControl Source # 
type Rep ObjectAccessControl = D1 (MetaData "ObjectAccessControl" "Network.Google.Storage.Types.Product" "gogol-storage-0.3.0-DGwRnfj7WmaH5CaBqC8AR9" False) (C1 (MetaCons "ObjectAccessControl'" PrefixI True) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_oacaEmail") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_oacaEtag") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_oacaKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_oacaDomain") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_oacaBucket") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_oacaRole") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_oacaSelfLink") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_oacaObject") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_oacaId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_oacaProjectTeam") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ObjectAccessControlProjectTeam))) (S1 (MetaSel (Just Symbol "_oacaEntity") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_oacaGeneration") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) (S1 (MetaSel (Just Symbol "_oacaEntityId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))))))

objectAccessControl :: ObjectAccessControl Source #

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

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

oacaEmail :: Lens' ObjectAccessControl (Maybe Text) Source #

The email address associated with the entity, if any.

oacaEtag :: Lens' ObjectAccessControl (Maybe Text) Source #

HTTP 1.1 Entity tag for the access-control entry.

oacaKind :: Lens' ObjectAccessControl Text Source #

The kind of item this is. For object access control entries, this is always storage#objectAccessControl.

oacaDomain :: Lens' ObjectAccessControl (Maybe Text) Source #

The domain associated with the entity, if any.

oacaBucket :: Lens' ObjectAccessControl (Maybe Text) Source #

The name of the bucket.

oacaRole :: Lens' ObjectAccessControl (Maybe Text) Source #

The access permission for the entity.

oacaSelfLink :: Lens' ObjectAccessControl (Maybe Text) Source #

The link to this access-control entry.

oacaObject :: Lens' ObjectAccessControl (Maybe Text) Source #

The name of the object, if applied to an object.

oacaId :: Lens' ObjectAccessControl (Maybe Text) Source #

The ID of the access-control entry.

oacaProjectTeam :: Lens' ObjectAccessControl (Maybe ObjectAccessControlProjectTeam) Source #

The project team associated with the entity, if any.

oacaEntity :: Lens' ObjectAccessControl (Maybe Text) Source #

The entity holding the permission, in one of the following forms: - user-userId - user-email - group-groupId - group-email - domain-domain - project-team-projectId - allUsers - allAuthenticatedUsers Examples: - The user liz'example.com would be user-liz'example.com. - The group example'googlegroups.com would be group-example'googlegroups.com. - To refer to all members of the Google Apps for Business domain example.com, the entity would be domain-example.com.

oacaGeneration :: Lens' ObjectAccessControl (Maybe Int64) Source #

The content generation of the object, if applied to an object.

oacaEntityId :: Lens' ObjectAccessControl (Maybe Text) Source #

The ID for the entity, if any.

ObjectsCopyProjection

data ObjectsCopyProjection Source #

Set of properties to return. Defaults to noAcl, unless the object resource specifies the acl property, when it defaults to full.

Constructors

OCPFull

full Include all properties.

OCPNoACL

noAcl Omit the owner, acl property.

Instances

Enum ObjectsCopyProjection Source # 
Eq ObjectsCopyProjection Source # 
Data ObjectsCopyProjection Source # 

Methods

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

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

toConstr :: ObjectsCopyProjection -> Constr #

dataTypeOf :: ObjectsCopyProjection -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ObjectsCopyProjection Source # 
Read ObjectsCopyProjection Source # 
Show ObjectsCopyProjection Source # 
Generic ObjectsCopyProjection Source # 
Hashable ObjectsCopyProjection Source # 
ToJSON ObjectsCopyProjection Source # 
FromJSON ObjectsCopyProjection Source # 
FromHttpApiData ObjectsCopyProjection Source # 
ToHttpApiData ObjectsCopyProjection Source # 
type Rep ObjectsCopyProjection Source # 
type Rep ObjectsCopyProjection = D1 (MetaData "ObjectsCopyProjection" "Network.Google.Storage.Types.Sum" "gogol-storage-0.3.0-DGwRnfj7WmaH5CaBqC8AR9" False) ((:+:) (C1 (MetaCons "OCPFull" PrefixI False) U1) (C1 (MetaCons "OCPNoACL" PrefixI False) U1))

RewriteResponse

data RewriteResponse Source #

A rewrite response.

See: rewriteResponse smart constructor.

Instances

Eq RewriteResponse Source # 
Data RewriteResponse Source # 

Methods

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

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

toConstr :: RewriteResponse -> Constr #

dataTypeOf :: RewriteResponse -> DataType #

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

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

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

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

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

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

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

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

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

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

Show RewriteResponse Source # 
Generic RewriteResponse Source # 
ToJSON RewriteResponse Source # 
FromJSON RewriteResponse Source # 
type Rep RewriteResponse Source # 
type Rep RewriteResponse = D1 (MetaData "RewriteResponse" "Network.Google.Storage.Types.Product" "gogol-storage-0.3.0-DGwRnfj7WmaH5CaBqC8AR9" False) (C1 (MetaCons "RewriteResponse'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_rrKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) ((:*:) (S1 (MetaSel (Just Symbol "_rrDone") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) (S1 (MetaSel (Just Symbol "_rrResource") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Object))))) ((:*:) (S1 (MetaSel (Just Symbol "_rrObjectSize") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Word64)))) ((:*:) (S1 (MetaSel (Just Symbol "_rrTotalBytesRewritten") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Word64)))) (S1 (MetaSel (Just Symbol "_rrRewriteToken") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))))

rewriteResponse :: RewriteResponse Source #

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

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

rrKind :: Lens' RewriteResponse Text Source #

The kind of item this is.

rrDone :: Lens' RewriteResponse (Maybe Bool) Source #

true if the copy is finished; otherwise, false if the copy is in progress. This property is always present in the response.

rrResource :: Lens' RewriteResponse (Maybe Object) Source #

A resource containing the metadata for the copied-to object. This property is present in the response only when copying completes.

rrObjectSize :: Lens' RewriteResponse (Maybe Word64) Source #

The total size of the object being copied in bytes. This property is always present in the response.

rrTotalBytesRewritten :: Lens' RewriteResponse (Maybe Word64) Source #

The total bytes written so far, which can be used to provide a waiting user with a progress indicator. This property is always present in the response.

rrRewriteToken :: Lens' RewriteResponse (Maybe Text) Source #

A token to use in subsequent requests to continue copying data. This token is present in the response only when there is more data to copy.

ObjectsRewriteProjection

data ObjectsRewriteProjection Source #

Set of properties to return. Defaults to noAcl, unless the object resource specifies the acl property, when it defaults to full.

Constructors

ORPFull

full Include all properties.

ORPNoACL

noAcl Omit the owner, acl property.

Instances

Enum ObjectsRewriteProjection Source # 
Eq ObjectsRewriteProjection Source # 
Data ObjectsRewriteProjection Source # 

Methods

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

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

toConstr :: ObjectsRewriteProjection -> Constr #

dataTypeOf :: ObjectsRewriteProjection -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ObjectsRewriteProjection Source # 
Read ObjectsRewriteProjection Source # 
Show ObjectsRewriteProjection Source # 
Generic ObjectsRewriteProjection Source # 
Hashable ObjectsRewriteProjection Source # 
ToJSON ObjectsRewriteProjection Source # 
FromJSON ObjectsRewriteProjection Source # 
FromHttpApiData ObjectsRewriteProjection Source # 
ToHttpApiData ObjectsRewriteProjection Source # 
type Rep ObjectsRewriteProjection Source # 
type Rep ObjectsRewriteProjection = D1 (MetaData "ObjectsRewriteProjection" "Network.Google.Storage.Types.Sum" "gogol-storage-0.3.0-DGwRnfj7WmaH5CaBqC8AR9" False) ((:+:) (C1 (MetaCons "ORPFull" PrefixI False) U1) (C1 (MetaCons "ORPNoACL" PrefixI False) U1))