amazonka-s3-1.6.1: Amazon Simple Storage Service SDK.

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

Network.AWS.S3

Contents

Description

Amazon Simple Storage Service is storage for the Internet. Amazon S3 has a simple web services interface that you can use to store and retrieve any amount of data, at any time, from anywhere on the web. It gives any developer access to the same highly scalable, reliable, fast, inexpensive data storage infrastructure that Amazon uses to run its own global network of web sites. The service aims to maximize benefits of scale and to pass those benefits on to developers.

Synopsis

Service Configuration

s3 :: Service Source #

API version 2006-03-01 of the Amazon Simple Storage Service SDK configuration.

Errors

Error matchers are designed for use with the functions provided by Control.Exception.Lens. This allows catching (and rethrowing) service specific errors returned by S3.

BucketAlreadyOwnedByYou

_BucketAlreadyOwnedByYou :: AsError a => Getting (First ServiceError) a ServiceError Source #

Prism for BucketAlreadyOwnedByYou' errors.

ObjectAlreadyInActiveTierError

_ObjectAlreadyInActiveTierError :: AsError a => Getting (First ServiceError) a ServiceError Source #

This operation is not allowed against this storage tier

BucketAlreadyExists

_BucketAlreadyExists :: AsError a => Getting (First ServiceError) a ServiceError Source #

The requested bucket name is not available. The bucket namespace is shared by all users of the system. Please select a different name and try again.

ObjectNotInActiveTierError

_ObjectNotInActiveTierError :: AsError a => Getting (First ServiceError) a ServiceError Source #

The source object of the COPY operation is not in the active tier and is only stored in Amazon Glacier.

NoSuchUpload

_NoSuchUpload :: AsError a => Getting (First ServiceError) a ServiceError Source #

The specified multipart upload does not exist.

NoSuchBucket

_NoSuchBucket :: AsError a => Getting (First ServiceError) a ServiceError Source #

The specified bucket does not exist.

NoSuchKey

_NoSuchKey :: AsError a => Getting (First ServiceError) a ServiceError Source #

The specified key does not exist.

Waiters

Waiters poll by repeatedly sending a request until some remote success condition configured by the Wait specification is fulfilled. The Wait specification determines how many attempts should be made, in addition to delay and retry strategies.

ObjectNotExists

objectNotExists :: Wait HeadObject Source #

Polls HeadObject every 5 seconds until a successful state is reached. An error is returned after 20 failed checks.

BucketExists

bucketExists :: Wait HeadBucket Source #

Polls HeadBucket every 5 seconds until a successful state is reached. An error is returned after 20 failed checks.

ObjectExists

objectExists :: Wait HeadObject Source #

Polls HeadObject every 5 seconds until a successful state is reached. An error is returned after 20 failed checks.

BucketNotExists

bucketNotExists :: Wait HeadBucket Source #

Polls HeadBucket every 5 seconds until a successful state is reached. An error is returned after 20 failed checks.

Operations

Some AWS operations return results that are incomplete and require subsequent requests in order to obtain the entire result set. The process of sending subsequent requests to continue where a previous request left off is called pagination. For example, the ListObjects operation of Amazon S3 returns up to 1000 objects at a time, and you must send subsequent requests with the appropriate Marker in order to retrieve the next page of results.

Operations that have an AWSPager instance can transparently perform subsequent requests, correctly setting Markers and other request facets to iterate through the entire result set of a truncated API operation. Operations which support this have an additional note in the documentation.

Many operations have the ability to filter results on the server side. See the individual operation parameters for details.

PutBucketRequestPayment

PutObject

DeleteObject

PutBucketLogging

GetBucketMetricsConfiguration

ListBuckets

DeleteBucket

CreateBucket

DeleteBucketTagging

PutObjectACL

PutBucketTagging

GetBucketInventoryConfiguration

PutBucketInventoryConfiguration

GetBucketLocation

ListBucketInventoryConfigurations

DeleteBucketInventoryConfiguration

GetBucketNotificationConfiguration

PutBucketAccelerateConfiguration

PutBucketMetricsConfiguration

DeleteBucketMetricsConfiguration

ListObjectsV2 (Paginated)

GetObject

PutBucketReplication

GetBucketWebsite

GetBucketRequestPayment

DeleteBucketReplication

ListObjectVersions (Paginated)

HeadBucket

DeleteBucketLifecycle

PutBucketLifecycleConfiguration

PutBucketAnalyticsConfiguration

ListBucketAnalyticsConfigurations

DeleteBucketAnalyticsConfiguration

CreateMultipartUpload

UploadPart

SelectObjectContent

GetBucketReplication

PutBucketWebsite

DeleteBucketWebsite

CompleteMultipartUpload

ListMultipartUploads (Paginated)

ListObjects (Paginated)

DeleteBucketPolicy

GetBucketEncryption

AbortMultipartUpload

PutBucketPolicy

GetBucketAccelerateConfiguration

GetObjectTorrent

DeleteObjects

PutBucketNotificationConfiguration

GetBucketVersioning

DeleteBucketCORS

PutBucketCORS

GetBucketCORS

GetObjectACL

RestoreObject

HeadObject

PutBucketVersioning

GetBucketTagging

CopyObject

ListBucketMetricsConfigurations

GetBucketPolicy

PutBucketEncryption

DeleteBucketEncryption

GetBucketLogging

GetBucketACL

GetBucketLifecycleConfiguration

GetBucketAnalyticsConfiguration

GetObjectTagging

ListParts (Paginated)

DeleteObjectTagging

UploadPartCopy

PutObjectTagging

PutBucketACL

Types

Common

data Region #

The available AWS regions.

Constructors

NorthVirginia

US East ('us-east-1').

Ohio

US East ('us-east-2').

NorthCalifornia

US West ('us-west-1').

Oregon

US West ('us-west-2').

Montreal

Canada ('ca-central-1').

Tokyo

Asia Pacific ('ap-northeast-1').

Seoul

Asia Pacific ('ap-northeast-2').

Mumbai

Asia Pacific ('ap-south-1').

Singapore

Asia Pacific ('ap-southeast-1').

Sydney

Asia Pacific ('ap-southeast-2').

SaoPaulo

South America ('sa-east-1').

Ireland

EU ('eu-west-1').

London

EU ('eu-west-2').

Frankfurt

EU ('eu-central-1').

GovCloud

US GovCloud ('us-gov-west-1').

GovCloudFIPS

US GovCloud FIPS (S3 Only, 'fips-us-gov-west-1').

Beijing

China ('cn-north-1').

Instances
Bounded Region 
Instance details

Defined in Network.AWS.Types

Enum Region 
Instance details

Defined in Network.AWS.Types

Eq Region 
Instance details

Defined in Network.AWS.Types

Methods

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

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

Data Region 
Instance details

Defined in Network.AWS.Types

Methods

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

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

toConstr :: Region -> Constr #

dataTypeOf :: Region -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Region 
Instance details

Defined in Network.AWS.Types

Read Region 
Instance details

Defined in Network.AWS.Types

Show Region 
Instance details

Defined in Network.AWS.Types

Generic Region 
Instance details

Defined in Network.AWS.Types

Associated Types

type Rep Region :: Type -> Type #

Methods

from :: Region -> Rep Region x #

to :: Rep Region x -> Region #

Hashable Region 
Instance details

Defined in Network.AWS.Types

Methods

hashWithSalt :: Int -> Region -> Int #

hash :: Region -> Int #

ToJSON Region 
Instance details

Defined in Network.AWS.Types

FromJSON Region 
Instance details

Defined in Network.AWS.Types

FromXML Region 
Instance details

Defined in Network.AWS.Types

ToXML Region 
Instance details

Defined in Network.AWS.Types

Methods

toXML :: Region -> XML #

ToLog Region 
Instance details

Defined in Network.AWS.Types

Methods

build :: Region -> Builder #

ToByteString Region 
Instance details

Defined in Network.AWS.Types

Methods

toBS :: Region -> ByteString #

FromText Region 
Instance details

Defined in Network.AWS.Types

Methods

parser :: Parser Region #

ToText Region 
Instance details

Defined in Network.AWS.Types

Methods

toText :: Region -> Text #

NFData Region 
Instance details

Defined in Network.AWS.Types

Methods

rnf :: Region -> () #

type Rep Region 
Instance details

Defined in Network.AWS.Types

type Rep Region = D1 (MetaData "Region" "Network.AWS.Types" "amazonka-core-1.6.1-FZORvxk9gh76fGemhSgXQL" False) ((((C1 (MetaCons "NorthVirginia" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Ohio" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "NorthCalifornia" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Oregon" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "Montreal" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Tokyo" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "Seoul" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Mumbai" PrefixI False) (U1 :: Type -> Type)))) :+: (((C1 (MetaCons "Singapore" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Sydney" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "SaoPaulo" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Ireland" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "London" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Frankfurt" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "GovCloud" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "GovCloudFIPS" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Beijing" PrefixI False) (U1 :: Type -> Type))))))

newtype BucketName Source #

Constructors

BucketName Text 
Instances
Eq BucketName Source # 
Instance details

Defined in Network.AWS.S3.Internal

Data BucketName Source # 
Instance details

Defined in Network.AWS.S3.Internal

Methods

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

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

toConstr :: BucketName -> Constr #

dataTypeOf :: BucketName -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord BucketName Source # 
Instance details

Defined in Network.AWS.S3.Internal

Read BucketName Source # 
Instance details

Defined in Network.AWS.S3.Internal

Show BucketName Source # 
Instance details

Defined in Network.AWS.S3.Internal

IsString BucketName Source # 
Instance details

Defined in Network.AWS.S3.Internal

Generic BucketName Source # 
Instance details

Defined in Network.AWS.S3.Internal

Associated Types

type Rep BucketName :: Type -> Type #

Hashable BucketName Source # 
Instance details

Defined in Network.AWS.S3.Internal

FromJSON BucketName Source # 
Instance details

Defined in Network.AWS.S3.Internal

FromXML BucketName Source # 
Instance details

Defined in Network.AWS.S3.Internal

ToXML BucketName Source # 
Instance details

Defined in Network.AWS.S3.Internal

Methods

toXML :: BucketName -> XML #

ToLog BucketName Source # 
Instance details

Defined in Network.AWS.S3.Internal

Methods

build :: BucketName -> Builder #

ToQuery BucketName Source # 
Instance details

Defined in Network.AWS.S3.Internal

ToByteString BucketName Source # 
Instance details

Defined in Network.AWS.S3.Internal

FromText BucketName Source # 
Instance details

Defined in Network.AWS.S3.Internal

ToText BucketName Source # 
Instance details

Defined in Network.AWS.S3.Internal

Methods

toText :: BucketName -> Text #

NFData BucketName Source # 
Instance details

Defined in Network.AWS.S3.Internal

Methods

rnf :: BucketName -> () #

type Rep BucketName Source # 
Instance details

Defined in Network.AWS.S3.Internal

type Rep BucketName = D1 (MetaData "BucketName" "Network.AWS.S3.Internal" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" True) (C1 (MetaCons "BucketName" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

newtype ETag Source #

Constructors

ETag ByteString 
Instances
Eq ETag Source # 
Instance details

Defined in Network.AWS.S3.Internal

Methods

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

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

Data ETag Source # 
Instance details

Defined in Network.AWS.S3.Internal

Methods

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

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

toConstr :: ETag -> Constr #

dataTypeOf :: ETag -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ETag Source # 
Instance details

Defined in Network.AWS.S3.Internal

Methods

compare :: ETag -> ETag -> Ordering #

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

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

(>) :: ETag -> ETag -> Bool #

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

max :: ETag -> ETag -> ETag #

min :: ETag -> ETag -> ETag #

Read ETag Source # 
Instance details

Defined in Network.AWS.S3.Internal

Show ETag Source # 
Instance details

Defined in Network.AWS.S3.Internal

Methods

showsPrec :: Int -> ETag -> ShowS #

show :: ETag -> String #

showList :: [ETag] -> ShowS #

IsString ETag Source # 
Instance details

Defined in Network.AWS.S3.Internal

Methods

fromString :: String -> ETag #

Generic ETag Source # 
Instance details

Defined in Network.AWS.S3.Internal

Associated Types

type Rep ETag :: Type -> Type #

Methods

from :: ETag -> Rep ETag x #

to :: Rep ETag x -> ETag #

Hashable ETag Source # 
Instance details

Defined in Network.AWS.S3.Internal

Methods

hashWithSalt :: Int -> ETag -> Int #

hash :: ETag -> Int #

FromXML ETag Source # 
Instance details

Defined in Network.AWS.S3.Internal

Methods

parseXML :: [Node] -> Either String ETag #

ToXML ETag Source # 
Instance details

Defined in Network.AWS.S3.Internal

Methods

toXML :: ETag -> XML #

ToLog ETag Source # 
Instance details

Defined in Network.AWS.S3.Internal

Methods

build :: ETag -> Builder #

ToQuery ETag Source # 
Instance details

Defined in Network.AWS.S3.Internal

Methods

toQuery :: ETag -> QueryString #

ToByteString ETag Source # 
Instance details

Defined in Network.AWS.S3.Internal

Methods

toBS :: ETag -> ByteString #

FromText ETag Source # 
Instance details

Defined in Network.AWS.S3.Internal

Methods

parser :: Parser ETag #

ToText ETag Source # 
Instance details

Defined in Network.AWS.S3.Internal

Methods

toText :: ETag -> Text #

NFData ETag Source # 
Instance details

Defined in Network.AWS.S3.Internal

Methods

rnf :: ETag -> () #

type Rep ETag Source # 
Instance details

Defined in Network.AWS.S3.Internal

type Rep ETag = D1 (MetaData "ETag" "Network.AWS.S3.Internal" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" True) (C1 (MetaCons "ETag" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ByteString)))

newtype ObjectVersionId Source #

Constructors

ObjectVersionId Text 
Instances
Eq ObjectVersionId Source # 
Instance details

Defined in Network.AWS.S3.Internal

Data ObjectVersionId Source # 
Instance details

Defined in Network.AWS.S3.Internal

Methods

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

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

toConstr :: ObjectVersionId -> Constr #

dataTypeOf :: ObjectVersionId -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ObjectVersionId Source # 
Instance details

Defined in Network.AWS.S3.Internal

Read ObjectVersionId Source # 
Instance details

Defined in Network.AWS.S3.Internal

Show ObjectVersionId Source # 
Instance details

Defined in Network.AWS.S3.Internal

IsString ObjectVersionId Source # 
Instance details

Defined in Network.AWS.S3.Internal

Generic ObjectVersionId Source # 
Instance details

Defined in Network.AWS.S3.Internal

Associated Types

type Rep ObjectVersionId :: Type -> Type #

Hashable ObjectVersionId Source # 
Instance details

Defined in Network.AWS.S3.Internal

FromXML ObjectVersionId Source # 
Instance details

Defined in Network.AWS.S3.Internal

ToXML ObjectVersionId Source # 
Instance details

Defined in Network.AWS.S3.Internal

Methods

toXML :: ObjectVersionId -> XML #

ToLog ObjectVersionId Source # 
Instance details

Defined in Network.AWS.S3.Internal

ToQuery ObjectVersionId Source # 
Instance details

Defined in Network.AWS.S3.Internal

ToByteString ObjectVersionId Source # 
Instance details

Defined in Network.AWS.S3.Internal

FromText ObjectVersionId Source # 
Instance details

Defined in Network.AWS.S3.Internal

ToText ObjectVersionId Source # 
Instance details

Defined in Network.AWS.S3.Internal

NFData ObjectVersionId Source # 
Instance details

Defined in Network.AWS.S3.Internal

Methods

rnf :: ObjectVersionId -> () #

type Rep ObjectVersionId Source # 
Instance details

Defined in Network.AWS.S3.Internal

type Rep ObjectVersionId = D1 (MetaData "ObjectVersionId" "Network.AWS.S3.Internal" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" True) (C1 (MetaCons "ObjectVersionId" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

Bucket Location

newtype LocationConstraint Source #

Instances
Eq LocationConstraint Source # 
Instance details

Defined in Network.AWS.S3.Internal

Data LocationConstraint Source # 
Instance details

Defined in Network.AWS.S3.Internal

Methods

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

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

toConstr :: LocationConstraint -> Constr #

dataTypeOf :: LocationConstraint -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord LocationConstraint Source # 
Instance details

Defined in Network.AWS.S3.Internal

Read LocationConstraint Source # 
Instance details

Defined in Network.AWS.S3.Internal

Show LocationConstraint Source # 
Instance details

Defined in Network.AWS.S3.Internal

Generic LocationConstraint Source # 
Instance details

Defined in Network.AWS.S3.Internal

Associated Types

type Rep LocationConstraint :: Type -> Type #

Hashable LocationConstraint Source # 
Instance details

Defined in Network.AWS.S3.Internal

FromXML LocationConstraint Source # 
Instance details

Defined in Network.AWS.S3.Internal

ToXML LocationConstraint Source # 
Instance details

Defined in Network.AWS.S3.Internal

ToLog LocationConstraint Source # 
Instance details

Defined in Network.AWS.S3.Internal

ToByteString LocationConstraint Source # 
Instance details

Defined in Network.AWS.S3.Internal

FromText LocationConstraint Source # 
Instance details

Defined in Network.AWS.S3.Internal

ToText LocationConstraint Source # 
Instance details

Defined in Network.AWS.S3.Internal

NFData LocationConstraint Source # 
Instance details

Defined in Network.AWS.S3.Internal

Methods

rnf :: LocationConstraint -> () #

type Rep LocationConstraint Source # 
Instance details

Defined in Network.AWS.S3.Internal

type Rep LocationConstraint = D1 (MetaData "LocationConstraint" "Network.AWS.S3.Internal" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" True) (C1 (MetaCons "LocationConstraint" PrefixI True) (S1 (MetaSel (Just "constraintRegion") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Region)))

Object Key

newtype ObjectKey Source #

Constructors

ObjectKey Text 
Instances
Eq ObjectKey Source # 
Instance details

Defined in Network.AWS.S3.Internal

Data ObjectKey Source # 
Instance details

Defined in Network.AWS.S3.Internal

Methods

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

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

toConstr :: ObjectKey -> Constr #

dataTypeOf :: ObjectKey -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ObjectKey Source # 
Instance details

Defined in Network.AWS.S3.Internal

Read ObjectKey Source # 
Instance details

Defined in Network.AWS.S3.Internal

Show ObjectKey Source # 
Instance details

Defined in Network.AWS.S3.Internal

IsString ObjectKey Source # 
Instance details

Defined in Network.AWS.S3.Internal

Generic ObjectKey Source # 
Instance details

Defined in Network.AWS.S3.Internal

Associated Types

type Rep ObjectKey :: Type -> Type #

Hashable ObjectKey Source # 
Instance details

Defined in Network.AWS.S3.Internal

FromXML ObjectKey Source # 
Instance details

Defined in Network.AWS.S3.Internal

ToXML ObjectKey Source # 
Instance details

Defined in Network.AWS.S3.Internal

Methods

toXML :: ObjectKey -> XML #

ToLog ObjectKey Source # 
Instance details

Defined in Network.AWS.S3.Internal

Methods

build :: ObjectKey -> Builder #

ToPath ObjectKey Source # 
Instance details

Defined in Network.AWS.S3.Internal

ToQuery ObjectKey Source # 
Instance details

Defined in Network.AWS.S3.Internal

ToByteString ObjectKey Source # 
Instance details

Defined in Network.AWS.S3.Internal

Methods

toBS :: ObjectKey -> ByteString #

FromText ObjectKey Source # 
Instance details

Defined in Network.AWS.S3.Internal

ToText ObjectKey Source # 
Instance details

Defined in Network.AWS.S3.Internal

Methods

toText :: ObjectKey -> Text #

NFData ObjectKey Source # 
Instance details

Defined in Network.AWS.S3.Internal

Methods

rnf :: ObjectKey -> () #

type Rep ObjectKey Source # 
Instance details

Defined in Network.AWS.S3.Internal

type Rep ObjectKey = D1 (MetaData "ObjectKey" "Network.AWS.S3.Internal" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" True) (C1 (MetaCons "ObjectKey" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

keyPrefix :: Delimiter -> Traversal' ObjectKey Text Source #

Traverse the prefix of an object key.

The prefix is classified as the entirety of the object key minus the name. A leading prefix in the presence of a name, and no other delimiters is interpreted as a blank prefix.

>>> "/home/jsmith/base.wiki" ^? keyPrefix '/'
Just "/home/jsmith"
>>> "/home/jsmith/" ^? keyPrefix '/'
Just "/home/jsmith"
>>> "/home" ^? keyPrefix '/'
Nothing
>>> "/" ^? keyPrefix '/'
Nothing

keyName :: Delimiter -> Traversal' ObjectKey Text Source #

Traverse the name of an object key.

keyComponents :: Delimiter -> IndexedTraversal' Int ObjectKey Text Source #

Traverse the path components of an object key using the specified delimiter.

Website Endpoints

getWebsiteEndpoint :: Region -> Text Source #

Get the S3 website endpoint for a specific region.

When you configure your bucket as a website, the website is available using this region-specific website endpoint.

See: Amazon Simple Storage Service Website Endpoints.

AnalyticsS3ExportFileFormat

data AnalyticsS3ExportFileFormat Source #

Constructors

CSV 
Instances
Bounded AnalyticsS3ExportFileFormat Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Enum AnalyticsS3ExportFileFormat Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Eq AnalyticsS3ExportFileFormat Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Data AnalyticsS3ExportFileFormat Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

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

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

toConstr :: AnalyticsS3ExportFileFormat -> Constr #

dataTypeOf :: AnalyticsS3ExportFileFormat -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord AnalyticsS3ExportFileFormat Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Read AnalyticsS3ExportFileFormat Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Show AnalyticsS3ExportFileFormat Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Generic AnalyticsS3ExportFileFormat Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Associated Types

type Rep AnalyticsS3ExportFileFormat :: Type -> Type #

Hashable AnalyticsS3ExportFileFormat Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

FromXML AnalyticsS3ExportFileFormat Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToXML AnalyticsS3ExportFileFormat Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToHeader AnalyticsS3ExportFileFormat Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToQuery AnalyticsS3ExportFileFormat Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToByteString AnalyticsS3ExportFileFormat Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

FromText AnalyticsS3ExportFileFormat Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToText AnalyticsS3ExportFileFormat Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

NFData AnalyticsS3ExportFileFormat Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

type Rep AnalyticsS3ExportFileFormat Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

type Rep AnalyticsS3ExportFileFormat = D1 (MetaData "AnalyticsS3ExportFileFormat" "Network.AWS.S3.Types.Sum" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" False) (C1 (MetaCons "CSV" PrefixI False) (U1 :: Type -> Type))

BucketAccelerateStatus

data BucketAccelerateStatus Source #

Constructors

BASEnabled 
BASSuspended 
Instances
Bounded BucketAccelerateStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Enum BucketAccelerateStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Eq BucketAccelerateStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Data BucketAccelerateStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

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

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

toConstr :: BucketAccelerateStatus -> Constr #

dataTypeOf :: BucketAccelerateStatus -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord BucketAccelerateStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Read BucketAccelerateStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Show BucketAccelerateStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Generic BucketAccelerateStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Associated Types

type Rep BucketAccelerateStatus :: Type -> Type #

Hashable BucketAccelerateStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

FromXML BucketAccelerateStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToXML BucketAccelerateStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToHeader BucketAccelerateStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToQuery BucketAccelerateStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToByteString BucketAccelerateStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

FromText BucketAccelerateStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToText BucketAccelerateStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

NFData BucketAccelerateStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

rnf :: BucketAccelerateStatus -> () #

type Rep BucketAccelerateStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

type Rep BucketAccelerateStatus = D1 (MetaData "BucketAccelerateStatus" "Network.AWS.S3.Types.Sum" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" False) (C1 (MetaCons "BASEnabled" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "BASSuspended" PrefixI False) (U1 :: Type -> Type))

BucketCannedACL

data BucketCannedACL Source #

Instances
Bounded BucketCannedACL Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Enum BucketCannedACL Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Eq BucketCannedACL Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Data BucketCannedACL Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

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

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

toConstr :: BucketCannedACL -> Constr #

dataTypeOf :: BucketCannedACL -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord BucketCannedACL Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Read BucketCannedACL Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Show BucketCannedACL Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Generic BucketCannedACL Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Associated Types

type Rep BucketCannedACL :: Type -> Type #

Hashable BucketCannedACL Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToXML BucketCannedACL Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

toXML :: BucketCannedACL -> XML #

ToHeader BucketCannedACL Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToQuery BucketCannedACL Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToByteString BucketCannedACL Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

FromText BucketCannedACL Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToText BucketCannedACL Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

NFData BucketCannedACL Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

rnf :: BucketCannedACL -> () #

type Rep BucketCannedACL Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

type Rep BucketCannedACL = D1 (MetaData "BucketCannedACL" "Network.AWS.S3.Types.Sum" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" False) ((C1 (MetaCons "BAuthenticatedRead" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "BPrivate" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "BPublicRead" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "BPublicReadWrite" PrefixI False) (U1 :: Type -> Type)))

BucketLogsPermission

data BucketLogsPermission Source #

Constructors

FullControl 
Read 
Write 
Instances
Bounded BucketLogsPermission Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Enum BucketLogsPermission Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Eq BucketLogsPermission Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Data BucketLogsPermission Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

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

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

toConstr :: BucketLogsPermission -> Constr #

dataTypeOf :: BucketLogsPermission -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord BucketLogsPermission Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Read BucketLogsPermission Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Show BucketLogsPermission Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Generic BucketLogsPermission Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Associated Types

type Rep BucketLogsPermission :: Type -> Type #

Hashable BucketLogsPermission Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

FromXML BucketLogsPermission Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToXML BucketLogsPermission Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToHeader BucketLogsPermission Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToQuery BucketLogsPermission Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToByteString BucketLogsPermission Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

FromText BucketLogsPermission Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToText BucketLogsPermission Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

NFData BucketLogsPermission Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

rnf :: BucketLogsPermission -> () #

type Rep BucketLogsPermission Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

type Rep BucketLogsPermission = D1 (MetaData "BucketLogsPermission" "Network.AWS.S3.Types.Sum" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" False) (C1 (MetaCons "FullControl" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "Read" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Write" PrefixI False) (U1 :: Type -> Type)))

BucketVersioningStatus

data BucketVersioningStatus Source #

Constructors

BVSEnabled 
BVSSuspended 
Instances
Bounded BucketVersioningStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Enum BucketVersioningStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Eq BucketVersioningStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Data BucketVersioningStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

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

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

toConstr :: BucketVersioningStatus -> Constr #

dataTypeOf :: BucketVersioningStatus -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord BucketVersioningStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Read BucketVersioningStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Show BucketVersioningStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Generic BucketVersioningStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Associated Types

type Rep BucketVersioningStatus :: Type -> Type #

Hashable BucketVersioningStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

FromXML BucketVersioningStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToXML BucketVersioningStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToHeader BucketVersioningStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToQuery BucketVersioningStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToByteString BucketVersioningStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

FromText BucketVersioningStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToText BucketVersioningStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

NFData BucketVersioningStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

rnf :: BucketVersioningStatus -> () #

type Rep BucketVersioningStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

type Rep BucketVersioningStatus = D1 (MetaData "BucketVersioningStatus" "Network.AWS.S3.Types.Sum" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" False) (C1 (MetaCons "BVSEnabled" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "BVSSuspended" PrefixI False) (U1 :: Type -> Type))

CompressionType

data CompressionType Source #

Constructors

CTGzip 
CTNone 
Instances
Bounded CompressionType Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Enum CompressionType Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Eq CompressionType Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Data CompressionType Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

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

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

toConstr :: CompressionType -> Constr #

dataTypeOf :: CompressionType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord CompressionType Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Read CompressionType Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Show CompressionType Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Generic CompressionType Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Associated Types

type Rep CompressionType :: Type -> Type #

Hashable CompressionType Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToXML CompressionType Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

toXML :: CompressionType -> XML #

ToHeader CompressionType Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToQuery CompressionType Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToByteString CompressionType Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

FromText CompressionType Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToText CompressionType Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

NFData CompressionType Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

rnf :: CompressionType -> () #

type Rep CompressionType Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

type Rep CompressionType = D1 (MetaData "CompressionType" "Network.AWS.S3.Types.Sum" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" False) (C1 (MetaCons "CTGzip" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "CTNone" PrefixI False) (U1 :: Type -> Type))

EncodingType

data EncodingType Source #

Requests Amazon S3 to encode the object keys in the response and specifies the encoding method to use. An object key may contain any Unicode character; however, XML 1.0 parser cannot parse some characters, such as characters with an ASCII value from 0 to 10. For characters that are not supported in XML 1.0, you can add this parameter to request that Amazon S3 encode the keys in the response.

Constructors

URL 
Instances
Bounded EncodingType Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Enum EncodingType Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Eq EncodingType Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Data EncodingType Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

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

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

toConstr :: EncodingType -> Constr #

dataTypeOf :: EncodingType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord EncodingType Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Read EncodingType Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Show EncodingType Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Generic EncodingType Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Associated Types

type Rep EncodingType :: Type -> Type #

Hashable EncodingType Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

FromXML EncodingType Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToXML EncodingType Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

toXML :: EncodingType -> XML #

ToHeader EncodingType Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToQuery EncodingType Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToByteString EncodingType Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

FromText EncodingType Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToText EncodingType Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

toText :: EncodingType -> Text #

NFData EncodingType Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

rnf :: EncodingType -> () #

type Rep EncodingType Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

type Rep EncodingType = D1 (MetaData "EncodingType" "Network.AWS.S3.Types.Sum" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" False) (C1 (MetaCons "URL" PrefixI False) (U1 :: Type -> Type))

Event

data Event Source #

Bucket event for which to send notifications.

Instances
Bounded Event Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Enum Event Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Eq Event Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

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

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

Data Event Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

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

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

toConstr :: Event -> Constr #

dataTypeOf :: Event -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Event Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

compare :: Event -> Event -> Ordering #

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

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

(>) :: Event -> Event -> Bool #

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

max :: Event -> Event -> Event #

min :: Event -> Event -> Event #

Read Event Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Show Event Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

showsPrec :: Int -> Event -> ShowS #

show :: Event -> String #

showList :: [Event] -> ShowS #

Generic Event Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Associated Types

type Rep Event :: Type -> Type #

Methods

from :: Event -> Rep Event x #

to :: Rep Event x -> Event #

Hashable Event Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

hashWithSalt :: Int -> Event -> Int #

hash :: Event -> Int #

FromXML Event Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

parseXML :: [Node] -> Either String Event #

ToXML Event Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

toXML :: Event -> XML #

ToHeader Event Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

toHeader :: HeaderName -> Event -> [Header] #

ToQuery Event Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

toQuery :: Event -> QueryString #

ToByteString Event Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

toBS :: Event -> ByteString #

FromText Event Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

parser :: Parser Event #

ToText Event Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

toText :: Event -> Text #

NFData Event Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

rnf :: Event -> () #

type Rep Event Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

type Rep Event = D1 (MetaData "Event" "Network.AWS.S3.Types.Sum" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" False) (((C1 (MetaCons "S3ObjectCreated" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "S3ObjectCreatedCompleteMultipartUpload" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "S3ObjectCreatedCopy" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "S3ObjectCreatedPost" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "S3ObjectCreatedPut" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "S3ObjectRemoved" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "S3ObjectRemovedDelete" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "S3ObjectRemovedDeleteMarkerCreated" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "S3ReducedRedundancyLostObject" PrefixI False) (U1 :: Type -> Type)))))

ExpirationStatus

data ExpirationStatus Source #

Constructors

ESDisabled 
ESEnabled 
Instances
Bounded ExpirationStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Enum ExpirationStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Eq ExpirationStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Data ExpirationStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

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

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

toConstr :: ExpirationStatus -> Constr #

dataTypeOf :: ExpirationStatus -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ExpirationStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Read ExpirationStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Show ExpirationStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Generic ExpirationStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Associated Types

type Rep ExpirationStatus :: Type -> Type #

Hashable ExpirationStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

FromXML ExpirationStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToXML ExpirationStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToHeader ExpirationStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToQuery ExpirationStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToByteString ExpirationStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

FromText ExpirationStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToText ExpirationStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

NFData ExpirationStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

rnf :: ExpirationStatus -> () #

type Rep ExpirationStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

type Rep ExpirationStatus = D1 (MetaData "ExpirationStatus" "Network.AWS.S3.Types.Sum" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" False) (C1 (MetaCons "ESDisabled" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "ESEnabled" PrefixI False) (U1 :: Type -> Type))

ExpressionType

data ExpressionType Source #

Constructors

Sql 
Instances
Bounded ExpressionType Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Enum ExpressionType Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Eq ExpressionType Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Data ExpressionType Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

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

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

toConstr :: ExpressionType -> Constr #

dataTypeOf :: ExpressionType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ExpressionType Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Read ExpressionType Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Show ExpressionType Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Generic ExpressionType Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Associated Types

type Rep ExpressionType :: Type -> Type #

Hashable ExpressionType Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToXML ExpressionType Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

toXML :: ExpressionType -> XML #

ToHeader ExpressionType Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToQuery ExpressionType Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToByteString ExpressionType Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

FromText ExpressionType Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToText ExpressionType Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

NFData ExpressionType Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

rnf :: ExpressionType -> () #

type Rep ExpressionType Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

type Rep ExpressionType = D1 (MetaData "ExpressionType" "Network.AWS.S3.Types.Sum" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" False) (C1 (MetaCons "Sql" PrefixI False) (U1 :: Type -> Type))

FileHeaderInfo

data FileHeaderInfo Source #

Constructors

Ignore 
None 
Use 
Instances
Bounded FileHeaderInfo Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Enum FileHeaderInfo Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Eq FileHeaderInfo Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Data FileHeaderInfo Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

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

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

toConstr :: FileHeaderInfo -> Constr #

dataTypeOf :: FileHeaderInfo -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord FileHeaderInfo Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Read FileHeaderInfo Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Show FileHeaderInfo Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Generic FileHeaderInfo Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Associated Types

type Rep FileHeaderInfo :: Type -> Type #

Hashable FileHeaderInfo Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToXML FileHeaderInfo Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

toXML :: FileHeaderInfo -> XML #

ToHeader FileHeaderInfo Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToQuery FileHeaderInfo Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToByteString FileHeaderInfo Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

FromText FileHeaderInfo Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToText FileHeaderInfo Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

NFData FileHeaderInfo Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

rnf :: FileHeaderInfo -> () #

type Rep FileHeaderInfo Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

type Rep FileHeaderInfo = D1 (MetaData "FileHeaderInfo" "Network.AWS.S3.Types.Sum" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" False) (C1 (MetaCons "Ignore" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "None" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Use" PrefixI False) (U1 :: Type -> Type)))

FilterRuleName

data FilterRuleName Source #

Constructors

Prefix 
Suffix 
Instances
Bounded FilterRuleName Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Enum FilterRuleName Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Eq FilterRuleName Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Data FilterRuleName Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

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

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

toConstr :: FilterRuleName -> Constr #

dataTypeOf :: FilterRuleName -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord FilterRuleName Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Read FilterRuleName Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Show FilterRuleName Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Generic FilterRuleName Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Associated Types

type Rep FilterRuleName :: Type -> Type #

Hashable FilterRuleName Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

FromXML FilterRuleName Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToXML FilterRuleName Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

toXML :: FilterRuleName -> XML #

ToHeader FilterRuleName Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToQuery FilterRuleName Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToByteString FilterRuleName Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

FromText FilterRuleName Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToText FilterRuleName Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

NFData FilterRuleName Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

rnf :: FilterRuleName -> () #

type Rep FilterRuleName Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

type Rep FilterRuleName = D1 (MetaData "FilterRuleName" "Network.AWS.S3.Types.Sum" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" False) (C1 (MetaCons "Prefix" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Suffix" PrefixI False) (U1 :: Type -> Type))

InventoryFormat

data InventoryFormat Source #

Constructors

IFCSV 
IFOrc 
Instances
Bounded InventoryFormat Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Enum InventoryFormat Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Eq InventoryFormat Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Data InventoryFormat Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

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

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

toConstr :: InventoryFormat -> Constr #

dataTypeOf :: InventoryFormat -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord InventoryFormat Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Read InventoryFormat Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Show InventoryFormat Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Generic InventoryFormat Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Associated Types

type Rep InventoryFormat :: Type -> Type #

Hashable InventoryFormat Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

FromXML InventoryFormat Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToXML InventoryFormat Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

toXML :: InventoryFormat -> XML #

ToHeader InventoryFormat Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToQuery InventoryFormat Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToByteString InventoryFormat Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

FromText InventoryFormat Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToText InventoryFormat Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

NFData InventoryFormat Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

rnf :: InventoryFormat -> () #

type Rep InventoryFormat Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

type Rep InventoryFormat = D1 (MetaData "InventoryFormat" "Network.AWS.S3.Types.Sum" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" False) (C1 (MetaCons "IFCSV" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "IFOrc" PrefixI False) (U1 :: Type -> Type))

InventoryFrequency

data InventoryFrequency Source #

Constructors

Daily 
Weekly 
Instances
Bounded InventoryFrequency Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Enum InventoryFrequency Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Eq InventoryFrequency Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Data InventoryFrequency Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

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

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

toConstr :: InventoryFrequency -> Constr #

dataTypeOf :: InventoryFrequency -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord InventoryFrequency Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Read InventoryFrequency Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Show InventoryFrequency Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Generic InventoryFrequency Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Associated Types

type Rep InventoryFrequency :: Type -> Type #

Hashable InventoryFrequency Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

FromXML InventoryFrequency Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToXML InventoryFrequency Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToHeader InventoryFrequency Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToQuery InventoryFrequency Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToByteString InventoryFrequency Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

FromText InventoryFrequency Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToText InventoryFrequency Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

NFData InventoryFrequency Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

rnf :: InventoryFrequency -> () #

type Rep InventoryFrequency Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

type Rep InventoryFrequency = D1 (MetaData "InventoryFrequency" "Network.AWS.S3.Types.Sum" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" False) (C1 (MetaCons "Daily" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Weekly" PrefixI False) (U1 :: Type -> Type))

InventoryIncludedObjectVersions

data InventoryIncludedObjectVersions Source #

Constructors

All 
Current 
Instances
Bounded InventoryIncludedObjectVersions Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Enum InventoryIncludedObjectVersions Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Eq InventoryIncludedObjectVersions Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Data InventoryIncludedObjectVersions Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

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

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

toConstr :: InventoryIncludedObjectVersions -> Constr #

dataTypeOf :: InventoryIncludedObjectVersions -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord InventoryIncludedObjectVersions Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Read InventoryIncludedObjectVersions Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Show InventoryIncludedObjectVersions Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Generic InventoryIncludedObjectVersions Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Associated Types

type Rep InventoryIncludedObjectVersions :: Type -> Type #

Hashable InventoryIncludedObjectVersions Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

FromXML InventoryIncludedObjectVersions Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToXML InventoryIncludedObjectVersions Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToHeader InventoryIncludedObjectVersions Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToQuery InventoryIncludedObjectVersions Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToByteString InventoryIncludedObjectVersions Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

FromText InventoryIncludedObjectVersions Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToText InventoryIncludedObjectVersions Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

NFData InventoryIncludedObjectVersions Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

type Rep InventoryIncludedObjectVersions Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

type Rep InventoryIncludedObjectVersions = D1 (MetaData "InventoryIncludedObjectVersions" "Network.AWS.S3.Types.Sum" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" False) (C1 (MetaCons "All" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Current" PrefixI False) (U1 :: Type -> Type))

InventoryOptionalField

data InventoryOptionalField Source #

Instances
Bounded InventoryOptionalField Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Enum InventoryOptionalField Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Eq InventoryOptionalField Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Data InventoryOptionalField Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

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

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

toConstr :: InventoryOptionalField -> Constr #

dataTypeOf :: InventoryOptionalField -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord InventoryOptionalField Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Read InventoryOptionalField Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Show InventoryOptionalField Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Generic InventoryOptionalField Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Associated Types

type Rep InventoryOptionalField :: Type -> Type #

Hashable InventoryOptionalField Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

FromXML InventoryOptionalField Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToXML InventoryOptionalField Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToHeader InventoryOptionalField Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToQuery InventoryOptionalField Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToByteString InventoryOptionalField Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

FromText InventoryOptionalField Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToText InventoryOptionalField Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

NFData InventoryOptionalField Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

rnf :: InventoryOptionalField -> () #

type Rep InventoryOptionalField Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

type Rep InventoryOptionalField = D1 (MetaData "InventoryOptionalField" "Network.AWS.S3.Types.Sum" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" False) ((C1 (MetaCons "FieldETag" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "FieldEncryptionStatus" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "FieldIsMultipartUploaded" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "FieldLastModifiedDate" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "FieldReplicationStatus" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "FieldSize" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "FieldStorageClass" PrefixI False) (U1 :: Type -> Type))))

JSONType

data JSONType Source #

Constructors

Document 
Lines 
Instances
Bounded JSONType Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Enum JSONType Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Eq JSONType Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Data JSONType Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

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

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

toConstr :: JSONType -> Constr #

dataTypeOf :: JSONType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord JSONType Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Read JSONType Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Show JSONType Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Generic JSONType Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Associated Types

type Rep JSONType :: Type -> Type #

Methods

from :: JSONType -> Rep JSONType x #

to :: Rep JSONType x -> JSONType #

Hashable JSONType Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

hashWithSalt :: Int -> JSONType -> Int #

hash :: JSONType -> Int #

ToXML JSONType Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

toXML :: JSONType -> XML #

ToHeader JSONType Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

toHeader :: HeaderName -> JSONType -> [Header] #

ToQuery JSONType Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToByteString JSONType Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

toBS :: JSONType -> ByteString #

FromText JSONType Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToText JSONType Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

toText :: JSONType -> Text #

NFData JSONType Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

rnf :: JSONType -> () #

type Rep JSONType Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

type Rep JSONType = D1 (MetaData "JSONType" "Network.AWS.S3.Types.Sum" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" False) (C1 (MetaCons "Document" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Lines" PrefixI False) (U1 :: Type -> Type))

MFADelete

data MFADelete Source #

Constructors

MDDisabled 
MDEnabled 
Instances
Bounded MFADelete Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Enum MFADelete Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Eq MFADelete Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Data MFADelete Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

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

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

toConstr :: MFADelete -> Constr #

dataTypeOf :: MFADelete -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord MFADelete Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Read MFADelete Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Show MFADelete Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Generic MFADelete Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Associated Types

type Rep MFADelete :: Type -> Type #

Hashable MFADelete Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToXML MFADelete Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

toXML :: MFADelete -> XML #

ToHeader MFADelete Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToQuery MFADelete Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToByteString MFADelete Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

toBS :: MFADelete -> ByteString #

FromText MFADelete Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToText MFADelete Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

toText :: MFADelete -> Text #

NFData MFADelete Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

rnf :: MFADelete -> () #

type Rep MFADelete Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

type Rep MFADelete = D1 (MetaData "MFADelete" "Network.AWS.S3.Types.Sum" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" False) (C1 (MetaCons "MDDisabled" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "MDEnabled" PrefixI False) (U1 :: Type -> Type))

MFADeleteStatus

data MFADeleteStatus Source #

Constructors

MDSDisabled 
MDSEnabled 
Instances
Bounded MFADeleteStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Enum MFADeleteStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Eq MFADeleteStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Data MFADeleteStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

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

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

toConstr :: MFADeleteStatus -> Constr #

dataTypeOf :: MFADeleteStatus -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord MFADeleteStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Read MFADeleteStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Show MFADeleteStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Generic MFADeleteStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Associated Types

type Rep MFADeleteStatus :: Type -> Type #

Hashable MFADeleteStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

FromXML MFADeleteStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToHeader MFADeleteStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToQuery MFADeleteStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToByteString MFADeleteStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

FromText MFADeleteStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToText MFADeleteStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

NFData MFADeleteStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

rnf :: MFADeleteStatus -> () #

type Rep MFADeleteStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

type Rep MFADeleteStatus = D1 (MetaData "MFADeleteStatus" "Network.AWS.S3.Types.Sum" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" False) (C1 (MetaCons "MDSDisabled" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "MDSEnabled" PrefixI False) (U1 :: Type -> Type))

MetadataDirective

data MetadataDirective Source #

Constructors

MDCopy 
MDReplace 
Instances
Bounded MetadataDirective Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Enum MetadataDirective Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Eq MetadataDirective Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Data MetadataDirective Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

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

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

toConstr :: MetadataDirective -> Constr #

dataTypeOf :: MetadataDirective -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord MetadataDirective Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Read MetadataDirective Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Show MetadataDirective Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Generic MetadataDirective Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Associated Types

type Rep MetadataDirective :: Type -> Type #

Hashable MetadataDirective Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToXML MetadataDirective Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToHeader MetadataDirective Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToQuery MetadataDirective Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToByteString MetadataDirective Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

FromText MetadataDirective Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToText MetadataDirective Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

NFData MetadataDirective Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

rnf :: MetadataDirective -> () #

type Rep MetadataDirective Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

type Rep MetadataDirective = D1 (MetaData "MetadataDirective" "Network.AWS.S3.Types.Sum" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" False) (C1 (MetaCons "MDCopy" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "MDReplace" PrefixI False) (U1 :: Type -> Type))

ObjectCannedACL

data ObjectCannedACL Source #

Instances
Bounded ObjectCannedACL Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Enum ObjectCannedACL Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Eq ObjectCannedACL Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Data ObjectCannedACL Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

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

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

toConstr :: ObjectCannedACL -> Constr #

dataTypeOf :: ObjectCannedACL -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ObjectCannedACL Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Read ObjectCannedACL Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Show ObjectCannedACL Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Generic ObjectCannedACL Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Associated Types

type Rep ObjectCannedACL :: Type -> Type #

Hashable ObjectCannedACL Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToXML ObjectCannedACL Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

toXML :: ObjectCannedACL -> XML #

ToHeader ObjectCannedACL Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToQuery ObjectCannedACL Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToByteString ObjectCannedACL Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

FromText ObjectCannedACL Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToText ObjectCannedACL Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

NFData ObjectCannedACL Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

rnf :: ObjectCannedACL -> () #

type Rep ObjectCannedACL Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

type Rep ObjectCannedACL = D1 (MetaData "ObjectCannedACL" "Network.AWS.S3.Types.Sum" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" False) ((C1 (MetaCons "OAWSExecRead" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "OAuthenticatedRead" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "OBucketOwnerFullControl" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "OBucketOwnerRead" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "OPrivate" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "OPublicRead" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "OPublicReadWrite" PrefixI False) (U1 :: Type -> Type))))

ObjectStorageClass

data ObjectStorageClass Source #

Instances
Bounded ObjectStorageClass Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Enum ObjectStorageClass Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Eq ObjectStorageClass Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Data ObjectStorageClass Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

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

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

toConstr :: ObjectStorageClass -> Constr #

dataTypeOf :: ObjectStorageClass -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ObjectStorageClass Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Read ObjectStorageClass Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Show ObjectStorageClass Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Generic ObjectStorageClass Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Associated Types

type Rep ObjectStorageClass :: Type -> Type #

Hashable ObjectStorageClass Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

FromXML ObjectStorageClass Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToHeader ObjectStorageClass Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToQuery ObjectStorageClass Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToByteString ObjectStorageClass Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

FromText ObjectStorageClass Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToText ObjectStorageClass Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

NFData ObjectStorageClass Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

rnf :: ObjectStorageClass -> () #

type Rep ObjectStorageClass Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

type Rep ObjectStorageClass = D1 (MetaData "ObjectStorageClass" "Network.AWS.S3.Types.Sum" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" False) ((C1 (MetaCons "OSCGlacier" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "OSCReducedRedundancy" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "OSCStandard" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "OSCStandardIA" PrefixI False) (U1 :: Type -> Type)))

ObjectVersionStorageClass

data ObjectVersionStorageClass Source #

Constructors

OVSCStandard 
Instances
Bounded ObjectVersionStorageClass Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Enum ObjectVersionStorageClass Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Eq ObjectVersionStorageClass Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Data ObjectVersionStorageClass Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

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

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

toConstr :: ObjectVersionStorageClass -> Constr #

dataTypeOf :: ObjectVersionStorageClass -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ObjectVersionStorageClass Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Read ObjectVersionStorageClass Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Show ObjectVersionStorageClass Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Generic ObjectVersionStorageClass Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Associated Types

type Rep ObjectVersionStorageClass :: Type -> Type #

Hashable ObjectVersionStorageClass Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

FromXML ObjectVersionStorageClass Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToHeader ObjectVersionStorageClass Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToQuery ObjectVersionStorageClass Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToByteString ObjectVersionStorageClass Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

FromText ObjectVersionStorageClass Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToText ObjectVersionStorageClass Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

NFData ObjectVersionStorageClass Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

type Rep ObjectVersionStorageClass Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

type Rep ObjectVersionStorageClass = D1 (MetaData "ObjectVersionStorageClass" "Network.AWS.S3.Types.Sum" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" False) (C1 (MetaCons "OVSCStandard" PrefixI False) (U1 :: Type -> Type))

OwnerOverride

data OwnerOverride Source #

Constructors

Destination 
Instances
Bounded OwnerOverride Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Enum OwnerOverride Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Eq OwnerOverride Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Data OwnerOverride Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

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

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

toConstr :: OwnerOverride -> Constr #

dataTypeOf :: OwnerOverride -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord OwnerOverride Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Read OwnerOverride Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Show OwnerOverride Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Generic OwnerOverride Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Associated Types

type Rep OwnerOverride :: Type -> Type #

Hashable OwnerOverride Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

FromXML OwnerOverride Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToXML OwnerOverride Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

toXML :: OwnerOverride -> XML #

ToHeader OwnerOverride Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToQuery OwnerOverride Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToByteString OwnerOverride Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

FromText OwnerOverride Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToText OwnerOverride Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

toText :: OwnerOverride -> Text #

NFData OwnerOverride Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

rnf :: OwnerOverride -> () #

type Rep OwnerOverride Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

type Rep OwnerOverride = D1 (MetaData "OwnerOverride" "Network.AWS.S3.Types.Sum" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" False) (C1 (MetaCons "Destination" PrefixI False) (U1 :: Type -> Type))

Payer

data Payer Source #

Constructors

BucketOwner 
Requester 
Instances
Bounded Payer Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Enum Payer Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Eq Payer Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

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

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

Data Payer Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

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

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

toConstr :: Payer -> Constr #

dataTypeOf :: Payer -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Payer Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

compare :: Payer -> Payer -> Ordering #

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

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

(>) :: Payer -> Payer -> Bool #

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

max :: Payer -> Payer -> Payer #

min :: Payer -> Payer -> Payer #

Read Payer Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Show Payer Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

showsPrec :: Int -> Payer -> ShowS #

show :: Payer -> String #

showList :: [Payer] -> ShowS #

Generic Payer Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Associated Types

type Rep Payer :: Type -> Type #

Methods

from :: Payer -> Rep Payer x #

to :: Rep Payer x -> Payer #

Hashable Payer Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

hashWithSalt :: Int -> Payer -> Int #

hash :: Payer -> Int #

FromXML Payer Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

parseXML :: [Node] -> Either String Payer #

ToXML Payer Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

toXML :: Payer -> XML #

ToHeader Payer Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

toHeader :: HeaderName -> Payer -> [Header] #

ToQuery Payer Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

toQuery :: Payer -> QueryString #

ToByteString Payer Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

toBS :: Payer -> ByteString #

FromText Payer Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

parser :: Parser Payer #

ToText Payer Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

toText :: Payer -> Text #

NFData Payer Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

rnf :: Payer -> () #

type Rep Payer Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

type Rep Payer = D1 (MetaData "Payer" "Network.AWS.S3.Types.Sum" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" False) (C1 (MetaCons "BucketOwner" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Requester" PrefixI False) (U1 :: Type -> Type))

Permission

data Permission Source #

Instances
Bounded Permission Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Enum Permission Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Eq Permission Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Data Permission Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

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

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

toConstr :: Permission -> Constr #

dataTypeOf :: Permission -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Permission Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Read Permission Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Show Permission Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Generic Permission Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Associated Types

type Rep Permission :: Type -> Type #

Hashable Permission Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

FromXML Permission Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToXML Permission Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

toXML :: Permission -> XML #

ToHeader Permission Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToQuery Permission Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToByteString Permission Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

FromText Permission Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToText Permission Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

toText :: Permission -> Text #

NFData Permission Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

rnf :: Permission -> () #

type Rep Permission Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

type Rep Permission = D1 (MetaData "Permission" "Network.AWS.S3.Types.Sum" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" False) ((C1 (MetaCons "PFullControl" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "PRead" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "PReadAcp" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "PWrite" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "PWriteAcp" PrefixI False) (U1 :: Type -> Type))))

Protocol

data Protocol Source #

Constructors

HTTP 
HTTPS 
Instances
Bounded Protocol Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Enum Protocol Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Eq Protocol Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Data Protocol Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

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

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

toConstr :: Protocol -> Constr #

dataTypeOf :: Protocol -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Protocol Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Read Protocol Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Show Protocol Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Generic Protocol Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Associated Types

type Rep Protocol :: Type -> Type #

Methods

from :: Protocol -> Rep Protocol x #

to :: Rep Protocol x -> Protocol #

Hashable Protocol Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

hashWithSalt :: Int -> Protocol -> Int #

hash :: Protocol -> Int #

FromXML Protocol Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToXML Protocol Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

toXML :: Protocol -> XML #

ToHeader Protocol Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

toHeader :: HeaderName -> Protocol -> [Header] #

ToQuery Protocol Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToByteString Protocol Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

toBS :: Protocol -> ByteString #

FromText Protocol Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToText Protocol Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

toText :: Protocol -> Text #

NFData Protocol Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

rnf :: Protocol -> () #

type Rep Protocol Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

type Rep Protocol = D1 (MetaData "Protocol" "Network.AWS.S3.Types.Sum" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" False) (C1 (MetaCons "HTTP" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "HTTPS" PrefixI False) (U1 :: Type -> Type))

QuoteFields

data QuoteFields Source #

Constructors

ASNeeded 
Always 
Instances
Bounded QuoteFields Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Enum QuoteFields Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Eq QuoteFields Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Data QuoteFields Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

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

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

toConstr :: QuoteFields -> Constr #

dataTypeOf :: QuoteFields -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord QuoteFields Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Read QuoteFields Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Show QuoteFields Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Generic QuoteFields Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Associated Types

type Rep QuoteFields :: Type -> Type #

Hashable QuoteFields Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToXML QuoteFields Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

toXML :: QuoteFields -> XML #

ToHeader QuoteFields Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToQuery QuoteFields Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToByteString QuoteFields Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

FromText QuoteFields Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToText QuoteFields Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

toText :: QuoteFields -> Text #

NFData QuoteFields Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

rnf :: QuoteFields -> () #

type Rep QuoteFields Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

type Rep QuoteFields = D1 (MetaData "QuoteFields" "Network.AWS.S3.Types.Sum" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" False) (C1 (MetaCons "ASNeeded" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Always" PrefixI False) (U1 :: Type -> Type))

ReplicationRuleStatus

data ReplicationRuleStatus Source #

Constructors

Disabled 
Enabled 
Instances
Bounded ReplicationRuleStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Enum ReplicationRuleStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Eq ReplicationRuleStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Data ReplicationRuleStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

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

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

toConstr :: ReplicationRuleStatus -> Constr #

dataTypeOf :: ReplicationRuleStatus -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ReplicationRuleStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Read ReplicationRuleStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Show ReplicationRuleStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Generic ReplicationRuleStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Associated Types

type Rep ReplicationRuleStatus :: Type -> Type #

Hashable ReplicationRuleStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

FromXML ReplicationRuleStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToXML ReplicationRuleStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToHeader ReplicationRuleStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToQuery ReplicationRuleStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToByteString ReplicationRuleStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

FromText ReplicationRuleStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToText ReplicationRuleStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

NFData ReplicationRuleStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

rnf :: ReplicationRuleStatus -> () #

type Rep ReplicationRuleStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

type Rep ReplicationRuleStatus = D1 (MetaData "ReplicationRuleStatus" "Network.AWS.S3.Types.Sum" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" False) (C1 (MetaCons "Disabled" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Enabled" PrefixI False) (U1 :: Type -> Type))

ReplicationStatus

data ReplicationStatus Source #

Constructors

Completed 
Failed 
Pending 
Replica 
Instances
Bounded ReplicationStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Enum ReplicationStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Eq ReplicationStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Data ReplicationStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

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

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

toConstr :: ReplicationStatus -> Constr #

dataTypeOf :: ReplicationStatus -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ReplicationStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Read ReplicationStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Show ReplicationStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Generic ReplicationStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Associated Types

type Rep ReplicationStatus :: Type -> Type #

Hashable ReplicationStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

FromXML ReplicationStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToHeader ReplicationStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToQuery ReplicationStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToByteString ReplicationStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

FromText ReplicationStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToText ReplicationStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

NFData ReplicationStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

rnf :: ReplicationStatus -> () #

type Rep ReplicationStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

type Rep ReplicationStatus = D1 (MetaData "ReplicationStatus" "Network.AWS.S3.Types.Sum" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" False) ((C1 (MetaCons "Completed" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Failed" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "Pending" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Replica" PrefixI False) (U1 :: Type -> Type)))

RequestCharged

data RequestCharged Source #

If present, indicates that the requester was successfully charged for the request.

Constructors

RCRequester 
Instances
Bounded RequestCharged Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Enum RequestCharged Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Eq RequestCharged Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Data RequestCharged Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

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

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

toConstr :: RequestCharged -> Constr #

dataTypeOf :: RequestCharged -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord RequestCharged Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Read RequestCharged Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Show RequestCharged Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Generic RequestCharged Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Associated Types

type Rep RequestCharged :: Type -> Type #

Hashable RequestCharged Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

FromXML RequestCharged Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToHeader RequestCharged Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToQuery RequestCharged Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToByteString RequestCharged Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

FromText RequestCharged Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToText RequestCharged Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

NFData RequestCharged Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

rnf :: RequestCharged -> () #

type Rep RequestCharged Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

type Rep RequestCharged = D1 (MetaData "RequestCharged" "Network.AWS.S3.Types.Sum" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" False) (C1 (MetaCons "RCRequester" PrefixI False) (U1 :: Type -> Type))

RequestPayer

data RequestPayer Source #

Confirms that the requester knows that she or he will be charged for the request. Bucket owners need not specify this parameter in their requests. Documentation on downloading objects from requester pays buckets can be found at http://docs.aws.amazon.com/AmazonS3/latest/dev/ObjectsinRequesterPaysBuckets.html

Constructors

RPRequester 
Instances
Bounded RequestPayer Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Enum RequestPayer Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Eq RequestPayer Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Data RequestPayer Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

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

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

toConstr :: RequestPayer -> Constr #

dataTypeOf :: RequestPayer -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord RequestPayer Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Read RequestPayer Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Show RequestPayer Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Generic RequestPayer Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Associated Types

type Rep RequestPayer :: Type -> Type #

Hashable RequestPayer Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToXML RequestPayer Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

toXML :: RequestPayer -> XML #

ToHeader RequestPayer Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToQuery RequestPayer Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToByteString RequestPayer Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

FromText RequestPayer Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToText RequestPayer Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

toText :: RequestPayer -> Text #

NFData RequestPayer Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

rnf :: RequestPayer -> () #

type Rep RequestPayer Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

type Rep RequestPayer = D1 (MetaData "RequestPayer" "Network.AWS.S3.Types.Sum" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" False) (C1 (MetaCons "RPRequester" PrefixI False) (U1 :: Type -> Type))

RestoreRequestType

data RestoreRequestType Source #

Constructors

Select 
Instances
Bounded RestoreRequestType Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Enum RestoreRequestType Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Eq RestoreRequestType Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Data RestoreRequestType Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

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

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

toConstr :: RestoreRequestType -> Constr #

dataTypeOf :: RestoreRequestType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord RestoreRequestType Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Read RestoreRequestType Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Show RestoreRequestType Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Generic RestoreRequestType Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Associated Types

type Rep RestoreRequestType :: Type -> Type #

Hashable RestoreRequestType Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToXML RestoreRequestType Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToHeader RestoreRequestType Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToQuery RestoreRequestType Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToByteString RestoreRequestType Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

FromText RestoreRequestType Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToText RestoreRequestType Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

NFData RestoreRequestType Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

rnf :: RestoreRequestType -> () #

type Rep RestoreRequestType Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

type Rep RestoreRequestType = D1 (MetaData "RestoreRequestType" "Network.AWS.S3.Types.Sum" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" False) (C1 (MetaCons "Select" PrefixI False) (U1 :: Type -> Type))

ServerSideEncryption

data ServerSideEncryption Source #

Constructors

AES256 
AWSKMS 
Instances
Bounded ServerSideEncryption Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Enum ServerSideEncryption Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Eq ServerSideEncryption Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Data ServerSideEncryption Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

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

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

toConstr :: ServerSideEncryption -> Constr #

dataTypeOf :: ServerSideEncryption -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ServerSideEncryption Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Read ServerSideEncryption Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Show ServerSideEncryption Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Generic ServerSideEncryption Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Associated Types

type Rep ServerSideEncryption :: Type -> Type #

Hashable ServerSideEncryption Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

FromXML ServerSideEncryption Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToXML ServerSideEncryption Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToHeader ServerSideEncryption Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToQuery ServerSideEncryption Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToByteString ServerSideEncryption Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

FromText ServerSideEncryption Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToText ServerSideEncryption Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

NFData ServerSideEncryption Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

rnf :: ServerSideEncryption -> () #

type Rep ServerSideEncryption Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

type Rep ServerSideEncryption = D1 (MetaData "ServerSideEncryption" "Network.AWS.S3.Types.Sum" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" False) (C1 (MetaCons "AES256" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "AWSKMS" PrefixI False) (U1 :: Type -> Type))

SseKMSEncryptedObjectsStatus

data SseKMSEncryptedObjectsStatus Source #

Instances
Bounded SseKMSEncryptedObjectsStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Enum SseKMSEncryptedObjectsStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Eq SseKMSEncryptedObjectsStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Data SseKMSEncryptedObjectsStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

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

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

toConstr :: SseKMSEncryptedObjectsStatus -> Constr #

dataTypeOf :: SseKMSEncryptedObjectsStatus -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord SseKMSEncryptedObjectsStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Read SseKMSEncryptedObjectsStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Show SseKMSEncryptedObjectsStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Generic SseKMSEncryptedObjectsStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Associated Types

type Rep SseKMSEncryptedObjectsStatus :: Type -> Type #

Hashable SseKMSEncryptedObjectsStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

FromXML SseKMSEncryptedObjectsStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToXML SseKMSEncryptedObjectsStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToHeader SseKMSEncryptedObjectsStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToQuery SseKMSEncryptedObjectsStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToByteString SseKMSEncryptedObjectsStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

FromText SseKMSEncryptedObjectsStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToText SseKMSEncryptedObjectsStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

NFData SseKMSEncryptedObjectsStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

type Rep SseKMSEncryptedObjectsStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

type Rep SseKMSEncryptedObjectsStatus = D1 (MetaData "SseKMSEncryptedObjectsStatus" "Network.AWS.S3.Types.Sum" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" False) (C1 (MetaCons "SKEOSDisabled" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "SKEOSEnabled" PrefixI False) (U1 :: Type -> Type))

StorageClass

data StorageClass Source #

Instances
Bounded StorageClass Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Enum StorageClass Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Eq StorageClass Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Data StorageClass Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

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

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

toConstr :: StorageClass -> Constr #

dataTypeOf :: StorageClass -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord StorageClass Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Read StorageClass Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Show StorageClass Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Generic StorageClass Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Associated Types

type Rep StorageClass :: Type -> Type #

Hashable StorageClass Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

FromXML StorageClass Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToXML StorageClass Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

toXML :: StorageClass -> XML #

ToHeader StorageClass Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToQuery StorageClass Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToByteString StorageClass Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

FromText StorageClass Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToText StorageClass Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

toText :: StorageClass -> Text #

NFData StorageClass Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

rnf :: StorageClass -> () #

type Rep StorageClass Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

type Rep StorageClass = D1 (MetaData "StorageClass" "Network.AWS.S3.Types.Sum" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" False) ((C1 (MetaCons "OnezoneIA" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "ReducedRedundancy" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "Standard" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "StandardIA" PrefixI False) (U1 :: Type -> Type)))

StorageClassAnalysisSchemaVersion

data StorageClassAnalysisSchemaVersion Source #

Constructors

V1 
Instances
Bounded StorageClassAnalysisSchemaVersion Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Enum StorageClassAnalysisSchemaVersion Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Eq StorageClassAnalysisSchemaVersion Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Data StorageClassAnalysisSchemaVersion Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

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

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

toConstr :: StorageClassAnalysisSchemaVersion -> Constr #

dataTypeOf :: StorageClassAnalysisSchemaVersion -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord StorageClassAnalysisSchemaVersion Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Read StorageClassAnalysisSchemaVersion Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Show StorageClassAnalysisSchemaVersion Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Generic StorageClassAnalysisSchemaVersion Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Associated Types

type Rep StorageClassAnalysisSchemaVersion :: Type -> Type #

Hashable StorageClassAnalysisSchemaVersion Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

FromXML StorageClassAnalysisSchemaVersion Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToXML StorageClassAnalysisSchemaVersion Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToHeader StorageClassAnalysisSchemaVersion Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToQuery StorageClassAnalysisSchemaVersion Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToByteString StorageClassAnalysisSchemaVersion Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

FromText StorageClassAnalysisSchemaVersion Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToText StorageClassAnalysisSchemaVersion Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

NFData StorageClassAnalysisSchemaVersion Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

type Rep StorageClassAnalysisSchemaVersion Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

type Rep StorageClassAnalysisSchemaVersion = D1 (MetaData "StorageClassAnalysisSchemaVersion" "Network.AWS.S3.Types.Sum" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" False) (C1 (MetaCons "V1" PrefixI False) (U1 :: Type -> Type))

TaggingDirective

data TaggingDirective Source #

Constructors

Copy 
Replace 
Instances
Bounded TaggingDirective Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Enum TaggingDirective Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Eq TaggingDirective Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Data TaggingDirective Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

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

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

toConstr :: TaggingDirective -> Constr #

dataTypeOf :: TaggingDirective -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord TaggingDirective Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Read TaggingDirective Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Show TaggingDirective Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Generic TaggingDirective Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Associated Types

type Rep TaggingDirective :: Type -> Type #

Hashable TaggingDirective Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToXML TaggingDirective Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToHeader TaggingDirective Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToQuery TaggingDirective Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToByteString TaggingDirective Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

FromText TaggingDirective Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToText TaggingDirective Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

NFData TaggingDirective Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

rnf :: TaggingDirective -> () #

type Rep TaggingDirective Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

type Rep TaggingDirective = D1 (MetaData "TaggingDirective" "Network.AWS.S3.Types.Sum" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" False) (C1 (MetaCons "Copy" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Replace" PrefixI False) (U1 :: Type -> Type))

Tier

data Tier Source #

Constructors

TBulk 
TExpedited 
TStandard 
Instances
Bounded Tier Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Enum Tier Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

succ :: Tier -> Tier #

pred :: Tier -> Tier #

toEnum :: Int -> Tier #

fromEnum :: Tier -> Int #

enumFrom :: Tier -> [Tier] #

enumFromThen :: Tier -> Tier -> [Tier] #

enumFromTo :: Tier -> Tier -> [Tier] #

enumFromThenTo :: Tier -> Tier -> Tier -> [Tier] #

Eq Tier Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

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

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

Data Tier Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

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

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

toConstr :: Tier -> Constr #

dataTypeOf :: Tier -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Tier Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

compare :: Tier -> Tier -> Ordering #

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

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

(>) :: Tier -> Tier -> Bool #

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

max :: Tier -> Tier -> Tier #

min :: Tier -> Tier -> Tier #

Read Tier Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Show Tier Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

showsPrec :: Int -> Tier -> ShowS #

show :: Tier -> String #

showList :: [Tier] -> ShowS #

Generic Tier Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Associated Types

type Rep Tier :: Type -> Type #

Methods

from :: Tier -> Rep Tier x #

to :: Rep Tier x -> Tier #

Hashable Tier Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

hashWithSalt :: Int -> Tier -> Int #

hash :: Tier -> Int #

ToXML Tier Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

toXML :: Tier -> XML #

ToHeader Tier Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

toHeader :: HeaderName -> Tier -> [Header] #

ToQuery Tier Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

toQuery :: Tier -> QueryString #

ToByteString Tier Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

toBS :: Tier -> ByteString #

FromText Tier Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

parser :: Parser Tier #

ToText Tier Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

toText :: Tier -> Text #

NFData Tier Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

rnf :: Tier -> () #

type Rep Tier Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

type Rep Tier = D1 (MetaData "Tier" "Network.AWS.S3.Types.Sum" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" False) (C1 (MetaCons "TBulk" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "TExpedited" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "TStandard" PrefixI False) (U1 :: Type -> Type)))

TransitionStorageClass

data TransitionStorageClass Source #

Instances
Bounded TransitionStorageClass Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Enum TransitionStorageClass Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Eq TransitionStorageClass Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Data TransitionStorageClass Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

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

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

toConstr :: TransitionStorageClass -> Constr #

dataTypeOf :: TransitionStorageClass -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord TransitionStorageClass Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Read TransitionStorageClass Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Show TransitionStorageClass Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Generic TransitionStorageClass Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Associated Types

type Rep TransitionStorageClass :: Type -> Type #

Hashable TransitionStorageClass Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

FromXML TransitionStorageClass Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToXML TransitionStorageClass Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToHeader TransitionStorageClass Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToQuery TransitionStorageClass Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToByteString TransitionStorageClass Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

FromText TransitionStorageClass Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

ToText TransitionStorageClass Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

NFData TransitionStorageClass Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

rnf :: TransitionStorageClass -> () #

type Rep TransitionStorageClass Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

type Rep TransitionStorageClass = D1 (MetaData "TransitionStorageClass" "Network.AWS.S3.Types.Sum" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" False) (C1 (MetaCons "TSCGlacier" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "TSCOnezoneIA" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "TSCStandardIA" PrefixI False) (U1 :: Type -> Type)))

Type

data Type Source #

Instances
Bounded Type Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Enum Type Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

succ :: Type -> Type #

pred :: Type -> Type #

toEnum :: Int -> Type #

fromEnum :: Type -> Int #

enumFrom :: Type -> [Type] #

enumFromThen :: Type -> Type -> [Type] #

enumFromTo :: Type -> Type -> [Type] #

enumFromThenTo :: Type -> Type -> Type -> [Type] #

Eq Type Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

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

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

Data Type Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

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

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

toConstr :: Type -> Constr #

dataTypeOf :: Type -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Type Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

compare :: Type -> Type -> Ordering #

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

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

(>) :: Type -> Type -> Bool #

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

max :: Type -> Type -> Type #

min :: Type -> Type -> Type #

Read Type Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Show Type Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

showsPrec :: Int -> Type -> ShowS #

show :: Type -> String #

showList :: [Type] -> ShowS #

Generic Type Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Associated Types

type Rep Type :: Type -> Type #

Methods

from :: Type -> Rep Type x #

to :: Rep Type x -> Type #

Hashable Type Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

hashWithSalt :: Int -> Type -> Int #

hash :: Type -> Int #

FromXML Type Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

parseXML :: [Node] -> Either String Type #

ToXML Type Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

toXML :: Type -> XML #

ToHeader Type Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

toHeader :: HeaderName -> Type -> [Header] #

ToQuery Type Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

toQuery :: Type -> QueryString #

ToByteString Type Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

toBS :: Type -> ByteString #

FromText Type Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

parser :: Parser Type #

ToText Type Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

toText :: Type -> Text #

NFData Type Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

Methods

rnf :: Type -> () #

type Rep Type Source # 
Instance details

Defined in Network.AWS.S3.Types.Sum

type Rep Type = D1 (MetaData "Type" "Network.AWS.S3.Types.Sum" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" False) (C1 (MetaCons "AmazonCustomerByEmail" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "CanonicalUser" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Group" PrefixI False) (U1 :: Type -> Type)))

AbortIncompleteMultipartUpload

data AbortIncompleteMultipartUpload Source #

Specifies the days since the initiation of an Incomplete Multipart Upload that Lifecycle will wait before permanently removing all parts of the upload.

See: abortIncompleteMultipartUpload smart constructor.

Instances
Eq AbortIncompleteMultipartUpload Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Data AbortIncompleteMultipartUpload Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

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

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

toConstr :: AbortIncompleteMultipartUpload -> Constr #

dataTypeOf :: AbortIncompleteMultipartUpload -> DataType #

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

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

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

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

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

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

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

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

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

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

Read AbortIncompleteMultipartUpload Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Show AbortIncompleteMultipartUpload Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Generic AbortIncompleteMultipartUpload Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Associated Types

type Rep AbortIncompleteMultipartUpload :: Type -> Type #

Hashable AbortIncompleteMultipartUpload Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

FromXML AbortIncompleteMultipartUpload Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

ToXML AbortIncompleteMultipartUpload Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

NFData AbortIncompleteMultipartUpload Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

type Rep AbortIncompleteMultipartUpload Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

type Rep AbortIncompleteMultipartUpload = D1 (MetaData "AbortIncompleteMultipartUpload" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" True) (C1 (MetaCons "AbortIncompleteMultipartUpload'" PrefixI True) (S1 (MetaSel (Just "_aimuDaysAfterInitiation") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Int))))

abortIncompleteMultipartUpload :: AbortIncompleteMultipartUpload Source #

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

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

  • aimuDaysAfterInitiation - Indicates the number of days that must pass since initiation for Lifecycle to abort an Incomplete Multipart Upload.

aimuDaysAfterInitiation :: Lens' AbortIncompleteMultipartUpload (Maybe Int) Source #

Indicates the number of days that must pass since initiation for Lifecycle to abort an Incomplete Multipart Upload.

AccelerateConfiguration

data AccelerateConfiguration Source #

See: accelerateConfiguration smart constructor.

Instances
Eq AccelerateConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Data AccelerateConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

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

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

toConstr :: AccelerateConfiguration -> Constr #

dataTypeOf :: AccelerateConfiguration -> DataType #

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

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

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

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

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

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

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

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

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

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

Read AccelerateConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Show AccelerateConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Generic AccelerateConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Associated Types

type Rep AccelerateConfiguration :: Type -> Type #

Hashable AccelerateConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

ToXML AccelerateConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

NFData AccelerateConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

rnf :: AccelerateConfiguration -> () #

type Rep AccelerateConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

type Rep AccelerateConfiguration = D1 (MetaData "AccelerateConfiguration" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" True) (C1 (MetaCons "AccelerateConfiguration'" PrefixI True) (S1 (MetaSel (Just "_acStatus") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe BucketAccelerateStatus))))

accelerateConfiguration :: AccelerateConfiguration Source #

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

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

  • acStatus - The accelerate configuration of the bucket.

acStatus :: Lens' AccelerateConfiguration (Maybe BucketAccelerateStatus) Source #

The accelerate configuration of the bucket.

AccessControlPolicy

data AccessControlPolicy Source #

See: accessControlPolicy smart constructor.

Instances
Eq AccessControlPolicy Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Data AccessControlPolicy Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

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

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

toConstr :: AccessControlPolicy -> Constr #

dataTypeOf :: AccessControlPolicy -> DataType #

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

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

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

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

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

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

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

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

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

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

Read AccessControlPolicy Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Show AccessControlPolicy Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Generic AccessControlPolicy Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Associated Types

type Rep AccessControlPolicy :: Type -> Type #

Hashable AccessControlPolicy Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

ToXML AccessControlPolicy Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

NFData AccessControlPolicy Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

rnf :: AccessControlPolicy -> () #

type Rep AccessControlPolicy Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

type Rep AccessControlPolicy = D1 (MetaData "AccessControlPolicy" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" False) (C1 (MetaCons "AccessControlPolicy'" PrefixI True) (S1 (MetaSel (Just "_acpGrants") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Grant])) :*: S1 (MetaSel (Just "_acpOwner") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Owner))))

accessControlPolicy :: AccessControlPolicy Source #

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

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

AccessControlTranslation

data AccessControlTranslation Source #

Container for information regarding the access control for replicas.

See: accessControlTranslation smart constructor.

Instances
Eq AccessControlTranslation Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Data AccessControlTranslation Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

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

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

toConstr :: AccessControlTranslation -> Constr #

dataTypeOf :: AccessControlTranslation -> DataType #

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

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

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

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

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

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

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

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

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

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

Read AccessControlTranslation Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Show AccessControlTranslation Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Generic AccessControlTranslation Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Associated Types

type Rep AccessControlTranslation :: Type -> Type #

Hashable AccessControlTranslation Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

FromXML AccessControlTranslation Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

ToXML AccessControlTranslation Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

NFData AccessControlTranslation Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

type Rep AccessControlTranslation Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

type Rep AccessControlTranslation = D1 (MetaData "AccessControlTranslation" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" True) (C1 (MetaCons "AccessControlTranslation'" PrefixI True) (S1 (MetaSel (Just "_actOwner") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 OwnerOverride)))

accessControlTranslation Source #

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

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

  • actOwner - The override value for the owner of the replica object.

actOwner :: Lens' AccessControlTranslation OwnerOverride Source #

The override value for the owner of the replica object.

AnalyticsAndOperator

data AnalyticsAndOperator Source #

See: analyticsAndOperator smart constructor.

Instances
Eq AnalyticsAndOperator Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Data AnalyticsAndOperator Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

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

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

toConstr :: AnalyticsAndOperator -> Constr #

dataTypeOf :: AnalyticsAndOperator -> DataType #

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

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

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

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

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

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

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

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

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

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

Read AnalyticsAndOperator Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Show AnalyticsAndOperator Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Generic AnalyticsAndOperator Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Associated Types

type Rep AnalyticsAndOperator :: Type -> Type #

Hashable AnalyticsAndOperator Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

FromXML AnalyticsAndOperator Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

ToXML AnalyticsAndOperator Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

NFData AnalyticsAndOperator Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

rnf :: AnalyticsAndOperator -> () #

type Rep AnalyticsAndOperator Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

type Rep AnalyticsAndOperator = D1 (MetaData "AnalyticsAndOperator" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" False) (C1 (MetaCons "AnalyticsAndOperator'" PrefixI True) (S1 (MetaSel (Just "_aaoPrefix") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_aaoTags") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Tag]))))

analyticsAndOperator :: AnalyticsAndOperator Source #

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

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

  • aaoPrefix - The prefix to use when evaluating an AND predicate.
  • aaoTags - The list of tags to use when evaluating an AND predicate.

aaoPrefix :: Lens' AnalyticsAndOperator (Maybe Text) Source #

The prefix to use when evaluating an AND predicate.

aaoTags :: Lens' AnalyticsAndOperator [Tag] Source #

The list of tags to use when evaluating an AND predicate.

AnalyticsConfiguration

data AnalyticsConfiguration Source #

See: analyticsConfiguration smart constructor.

Instances
Eq AnalyticsConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Data AnalyticsConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

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

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

toConstr :: AnalyticsConfiguration -> Constr #

dataTypeOf :: AnalyticsConfiguration -> DataType #

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

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

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

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

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

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

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

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

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

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

Read AnalyticsConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Show AnalyticsConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Generic AnalyticsConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Associated Types

type Rep AnalyticsConfiguration :: Type -> Type #

Hashable AnalyticsConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

FromXML AnalyticsConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

ToXML AnalyticsConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

NFData AnalyticsConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

rnf :: AnalyticsConfiguration -> () #

type Rep AnalyticsConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

type Rep AnalyticsConfiguration = D1 (MetaData "AnalyticsConfiguration" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" False) (C1 (MetaCons "AnalyticsConfiguration'" PrefixI True) (S1 (MetaSel (Just "_acFilter") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe AnalyticsFilter)) :*: (S1 (MetaSel (Just "_acId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text) :*: S1 (MetaSel (Just "_acStorageClassAnalysis") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 StorageClassAnalysis))))

analyticsConfiguration Source #

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

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

  • acFilter - The filter used to describe a set of objects for analyses. A filter must have exactly one prefix, one tag, or one conjunction (AnalyticsAndOperator). If no filter is provided, all objects will be considered in any analysis.
  • acId - The identifier used to represent an analytics configuration.
  • acStorageClassAnalysis - If present, it indicates that data related to access patterns will be collected and made available to analyze the tradeoffs between different storage classes.

acFilter :: Lens' AnalyticsConfiguration (Maybe AnalyticsFilter) Source #

The filter used to describe a set of objects for analyses. A filter must have exactly one prefix, one tag, or one conjunction (AnalyticsAndOperator). If no filter is provided, all objects will be considered in any analysis.

acId :: Lens' AnalyticsConfiguration Text Source #

The identifier used to represent an analytics configuration.

acStorageClassAnalysis :: Lens' AnalyticsConfiguration StorageClassAnalysis Source #

If present, it indicates that data related to access patterns will be collected and made available to analyze the tradeoffs between different storage classes.

AnalyticsExportDestination

data AnalyticsExportDestination Source #

See: analyticsExportDestination smart constructor.

Instances
Eq AnalyticsExportDestination Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Data AnalyticsExportDestination Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

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

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

toConstr :: AnalyticsExportDestination -> Constr #

dataTypeOf :: AnalyticsExportDestination -> DataType #

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

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

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

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

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

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

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

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

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

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

Read AnalyticsExportDestination Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Show AnalyticsExportDestination Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Generic AnalyticsExportDestination Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Associated Types

type Rep AnalyticsExportDestination :: Type -> Type #

Hashable AnalyticsExportDestination Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

FromXML AnalyticsExportDestination Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

ToXML AnalyticsExportDestination Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

NFData AnalyticsExportDestination Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

type Rep AnalyticsExportDestination Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

type Rep AnalyticsExportDestination = D1 (MetaData "AnalyticsExportDestination" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" True) (C1 (MetaCons "AnalyticsExportDestination'" PrefixI True) (S1 (MetaSel (Just "_aedS3BucketDestination") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 AnalyticsS3BucketDestination)))

analyticsExportDestination Source #

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

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

AnalyticsFilter

data AnalyticsFilter Source #

See: analyticsFilter smart constructor.

Instances
Eq AnalyticsFilter Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Data AnalyticsFilter Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

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

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

toConstr :: AnalyticsFilter -> Constr #

dataTypeOf :: AnalyticsFilter -> DataType #

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

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

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

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

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

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

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

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

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

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

Read AnalyticsFilter Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Show AnalyticsFilter Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Generic AnalyticsFilter Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Associated Types

type Rep AnalyticsFilter :: Type -> Type #

Hashable AnalyticsFilter Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

FromXML AnalyticsFilter Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

ToXML AnalyticsFilter Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

toXML :: AnalyticsFilter -> XML #

NFData AnalyticsFilter Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

rnf :: AnalyticsFilter -> () #

type Rep AnalyticsFilter Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

type Rep AnalyticsFilter = D1 (MetaData "AnalyticsFilter" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" False) (C1 (MetaCons "AnalyticsFilter'" PrefixI True) (S1 (MetaSel (Just "_afTag") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Tag)) :*: (S1 (MetaSel (Just "_afPrefix") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_afAnd") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe AnalyticsAndOperator)))))

analyticsFilter :: AnalyticsFilter Source #

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

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

  • afTag - The tag to use when evaluating an analytics filter.
  • afPrefix - The prefix to use when evaluating an analytics filter.
  • afAnd - A conjunction (logical AND) of predicates, which is used in evaluating an analytics filter. The operator must have at least two predicates.

afTag :: Lens' AnalyticsFilter (Maybe Tag) Source #

The tag to use when evaluating an analytics filter.

afPrefix :: Lens' AnalyticsFilter (Maybe Text) Source #

The prefix to use when evaluating an analytics filter.

afAnd :: Lens' AnalyticsFilter (Maybe AnalyticsAndOperator) Source #

A conjunction (logical AND) of predicates, which is used in evaluating an analytics filter. The operator must have at least two predicates.

AnalyticsS3BucketDestination

data AnalyticsS3BucketDestination Source #

See: analyticsS3BucketDestination smart constructor.

Instances
Eq AnalyticsS3BucketDestination Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Data AnalyticsS3BucketDestination Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

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

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

toConstr :: AnalyticsS3BucketDestination -> Constr #

dataTypeOf :: AnalyticsS3BucketDestination -> DataType #

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

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

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

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

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

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

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

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

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

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

Read AnalyticsS3BucketDestination Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Show AnalyticsS3BucketDestination Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Generic AnalyticsS3BucketDestination Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Associated Types

type Rep AnalyticsS3BucketDestination :: Type -> Type #

Hashable AnalyticsS3BucketDestination Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

FromXML AnalyticsS3BucketDestination Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

ToXML AnalyticsS3BucketDestination Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

NFData AnalyticsS3BucketDestination Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

type Rep AnalyticsS3BucketDestination Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

type Rep AnalyticsS3BucketDestination = D1 (MetaData "AnalyticsS3BucketDestination" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" False) (C1 (MetaCons "AnalyticsS3BucketDestination'" PrefixI True) ((S1 (MetaSel (Just "_asbdBucketAccountId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_asbdPrefix") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) :*: (S1 (MetaSel (Just "_asbdFormat") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 AnalyticsS3ExportFileFormat) :*: S1 (MetaSel (Just "_asbdBucket") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 BucketName))))

analyticsS3BucketDestination Source #

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

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

  • asbdBucketAccountId - The account ID that owns the destination bucket. If no account ID is provided, the owner will not be validated prior to exporting data.
  • asbdPrefix - The prefix to use when exporting data. The exported data begins with this prefix.
  • asbdFormat - The file format used when exporting data to Amazon S3.
  • asbdBucket - The Amazon resource name (ARN) of the bucket to which data is exported.

asbdBucketAccountId :: Lens' AnalyticsS3BucketDestination (Maybe Text) Source #

The account ID that owns the destination bucket. If no account ID is provided, the owner will not be validated prior to exporting data.

asbdPrefix :: Lens' AnalyticsS3BucketDestination (Maybe Text) Source #

The prefix to use when exporting data. The exported data begins with this prefix.

asbdFormat :: Lens' AnalyticsS3BucketDestination AnalyticsS3ExportFileFormat Source #

The file format used when exporting data to Amazon S3.

asbdBucket :: Lens' AnalyticsS3BucketDestination BucketName Source #

The Amazon resource name (ARN) of the bucket to which data is exported.

Bucket

data Bucket Source #

See: bucket smart constructor.

Instances
Eq Bucket Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

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

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

Data Bucket Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

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 #

Read Bucket Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Show Bucket Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Generic Bucket Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Associated Types

type Rep Bucket :: Type -> Type #

Methods

from :: Bucket -> Rep Bucket x #

to :: Rep Bucket x -> Bucket #

Hashable Bucket Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

hashWithSalt :: Int -> Bucket -> Int #

hash :: Bucket -> Int #

FromXML Bucket Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

NFData Bucket Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

rnf :: Bucket -> () #

type Rep Bucket Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

type Rep Bucket = D1 (MetaData "Bucket" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" False) (C1 (MetaCons "Bucket'" PrefixI True) (S1 (MetaSel (Just "_bCreationDate") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 RFC822) :*: S1 (MetaSel (Just "_bName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 BucketName)))

bucket Source #

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

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

bCreationDate :: Lens' Bucket UTCTime Source #

Date the bucket was created.

bName :: Lens' Bucket BucketName Source #

The name of the bucket.

BucketLifecycleConfiguration

data BucketLifecycleConfiguration Source #

See: bucketLifecycleConfiguration smart constructor.

Instances
Eq BucketLifecycleConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Data BucketLifecycleConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

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

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

toConstr :: BucketLifecycleConfiguration -> Constr #

dataTypeOf :: BucketLifecycleConfiguration -> DataType #

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

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

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

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

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

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

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

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

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

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

Read BucketLifecycleConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Show BucketLifecycleConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Generic BucketLifecycleConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Associated Types

type Rep BucketLifecycleConfiguration :: Type -> Type #

Hashable BucketLifecycleConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

ToXML BucketLifecycleConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

NFData BucketLifecycleConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

type Rep BucketLifecycleConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

type Rep BucketLifecycleConfiguration = D1 (MetaData "BucketLifecycleConfiguration" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" True) (C1 (MetaCons "BucketLifecycleConfiguration'" PrefixI True) (S1 (MetaSel (Just "_blcRules") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [LifecycleRule])))

bucketLifecycleConfiguration :: BucketLifecycleConfiguration Source #

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

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

BucketLoggingStatus

data BucketLoggingStatus Source #

See: bucketLoggingStatus smart constructor.

Instances
Eq BucketLoggingStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Data BucketLoggingStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

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

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

toConstr :: BucketLoggingStatus -> Constr #

dataTypeOf :: BucketLoggingStatus -> DataType #

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

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

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

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

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

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

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

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

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

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

Read BucketLoggingStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Show BucketLoggingStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Generic BucketLoggingStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Associated Types

type Rep BucketLoggingStatus :: Type -> Type #

Hashable BucketLoggingStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

ToXML BucketLoggingStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

NFData BucketLoggingStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

rnf :: BucketLoggingStatus -> () #

type Rep BucketLoggingStatus Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

type Rep BucketLoggingStatus = D1 (MetaData "BucketLoggingStatus" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" True) (C1 (MetaCons "BucketLoggingStatus'" PrefixI True) (S1 (MetaSel (Just "_blsLoggingEnabled") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe LoggingEnabled))))

bucketLoggingStatus :: BucketLoggingStatus Source #

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

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

CORSConfiguration

data CORSConfiguration Source #

See: corsConfiguration smart constructor.

Instances
Eq CORSConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Data CORSConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

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

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

toConstr :: CORSConfiguration -> Constr #

dataTypeOf :: CORSConfiguration -> DataType #

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

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

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

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

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

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

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

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

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

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

Read CORSConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Show CORSConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Generic CORSConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Associated Types

type Rep CORSConfiguration :: Type -> Type #

Hashable CORSConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

ToXML CORSConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

NFData CORSConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

rnf :: CORSConfiguration -> () #

type Rep CORSConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

type Rep CORSConfiguration = D1 (MetaData "CORSConfiguration" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" True) (C1 (MetaCons "CORSConfiguration'" PrefixI True) (S1 (MetaSel (Just "_ccCORSRules") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [CORSRule])))

corsConfiguration :: CORSConfiguration Source #

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

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

CORSRule

data CORSRule Source #

See: corsRule smart constructor.

Instances
Eq CORSRule Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Data CORSRule Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

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

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

toConstr :: CORSRule -> Constr #

dataTypeOf :: CORSRule -> DataType #

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

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

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

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

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

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

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

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

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

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

Read CORSRule Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Show CORSRule Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Generic CORSRule Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Associated Types

type Rep CORSRule :: Type -> Type #

Methods

from :: CORSRule -> Rep CORSRule x #

to :: Rep CORSRule x -> CORSRule #

Hashable CORSRule Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

hashWithSalt :: Int -> CORSRule -> Int #

hash :: CORSRule -> Int #

FromXML CORSRule Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

ToXML CORSRule Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

toXML :: CORSRule -> XML #

NFData CORSRule Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

rnf :: CORSRule -> () #

type Rep CORSRule Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

type Rep CORSRule = D1 (MetaData "CORSRule" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" False) (C1 (MetaCons "CORSRule'" PrefixI True) ((S1 (MetaSel (Just "_crMaxAgeSeconds") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Int)) :*: S1 (MetaSel (Just "_crAllowedHeaders") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Text]))) :*: (S1 (MetaSel (Just "_crExposeHeaders") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Text])) :*: (S1 (MetaSel (Just "_crAllowedMethods") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [Text]) :*: S1 (MetaSel (Just "_crAllowedOrigins") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [Text])))))

corsRule :: CORSRule Source #

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

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

  • crMaxAgeSeconds - The time in seconds that your browser is to cache the preflight response for the specified resource.
  • crAllowedHeaders - Specifies which headers are allowed in a pre-flight OPTIONS request.
  • crExposeHeaders - One or more headers in the response that you want customers to be able to access from their applications (for example, from a JavaScript XMLHttpRequest object).
  • crAllowedMethods - Identifies HTTP methods that the domain/origin specified in the rule is allowed to execute.
  • crAllowedOrigins - One or more origins you want customers to be able to access the bucket from.

crMaxAgeSeconds :: Lens' CORSRule (Maybe Int) Source #

The time in seconds that your browser is to cache the preflight response for the specified resource.

crAllowedHeaders :: Lens' CORSRule [Text] Source #

Specifies which headers are allowed in a pre-flight OPTIONS request.

crExposeHeaders :: Lens' CORSRule [Text] Source #

One or more headers in the response that you want customers to be able to access from their applications (for example, from a JavaScript XMLHttpRequest object).

crAllowedMethods :: Lens' CORSRule [Text] Source #

Identifies HTTP methods that the domain/origin specified in the rule is allowed to execute.

crAllowedOrigins :: Lens' CORSRule [Text] Source #

One or more origins you want customers to be able to access the bucket from.

CSVInput

data CSVInput Source #

Describes how a CSV-formatted input object is formatted.

See: csvInput smart constructor.

Instances
Eq CSVInput Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Data CSVInput Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

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

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

toConstr :: CSVInput -> Constr #

dataTypeOf :: CSVInput -> DataType #

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

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

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

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

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

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

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

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

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

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

Read CSVInput Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Show CSVInput Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Generic CSVInput Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Associated Types

type Rep CSVInput :: Type -> Type #

Methods

from :: CSVInput -> Rep CSVInput x #

to :: Rep CSVInput x -> CSVInput #

Hashable CSVInput Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

hashWithSalt :: Int -> CSVInput -> Int #

hash :: CSVInput -> Int #

ToXML CSVInput Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

toXML :: CSVInput -> XML #

NFData CSVInput Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

rnf :: CSVInput -> () #

type Rep CSVInput Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

type Rep CSVInput = D1 (MetaData "CSVInput" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" False) (C1 (MetaCons "CSVInput'" PrefixI True) ((S1 (MetaSel (Just "_ciQuoteCharacter") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: (S1 (MetaSel (Just "_ciRecordDelimiter") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_ciFileHeaderInfo") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe FileHeaderInfo)))) :*: (S1 (MetaSel (Just "_ciQuoteEscapeCharacter") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: (S1 (MetaSel (Just "_ciComments") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_ciFieldDelimiter") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))))

csvInput :: CSVInput Source #

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

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

  • ciQuoteCharacter - Value used for escaping where the field delimiter is part of the value.
  • ciRecordDelimiter - Value used to separate individual records.
  • ciFileHeaderInfo - Describes the first line of input. Valid values: None, Ignore, Use.
  • ciQuoteEscapeCharacter - Single character used for escaping the quote character inside an already escaped value.
  • ciComments - Single character used to indicate a row should be ignored when present at the start of a row.
  • ciFieldDelimiter - Value used to separate individual fields in a record.

ciQuoteCharacter :: Lens' CSVInput (Maybe Text) Source #

Value used for escaping where the field delimiter is part of the value.

ciRecordDelimiter :: Lens' CSVInput (Maybe Text) Source #

Value used to separate individual records.

ciFileHeaderInfo :: Lens' CSVInput (Maybe FileHeaderInfo) Source #

Describes the first line of input. Valid values: None, Ignore, Use.

ciQuoteEscapeCharacter :: Lens' CSVInput (Maybe Text) Source #

Single character used for escaping the quote character inside an already escaped value.

ciComments :: Lens' CSVInput (Maybe Text) Source #

Single character used to indicate a row should be ignored when present at the start of a row.

ciFieldDelimiter :: Lens' CSVInput (Maybe Text) Source #

Value used to separate individual fields in a record.

CSVOutput

data CSVOutput Source #

Describes how CSV-formatted results are formatted.

See: csvOutput smart constructor.

Instances
Eq CSVOutput Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Data CSVOutput Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

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

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

toConstr :: CSVOutput -> Constr #

dataTypeOf :: CSVOutput -> DataType #

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

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

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

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

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

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

gmapQi :: Int -> (forall d. Data d => d -> u) -> CSVOutput -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CSVOutput -> m CSVOutput #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CSVOutput -> m CSVOutput #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CSVOutput -> m CSVOutput #

Read CSVOutput Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Show CSVOutput Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Generic CSVOutput Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Associated Types

type Rep CSVOutput :: Type -> Type #

Hashable CSVOutput Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

ToXML CSVOutput Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

toXML :: CSVOutput -> XML #

NFData CSVOutput Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

rnf :: CSVOutput -> () #

type Rep CSVOutput Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

type Rep CSVOutput = D1 (MetaData "CSVOutput" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" False) (C1 (MetaCons "CSVOutput'" PrefixI True) ((S1 (MetaSel (Just "_coQuoteCharacter") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_coQuoteFields") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe QuoteFields))) :*: (S1 (MetaSel (Just "_coRecordDelimiter") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: (S1 (MetaSel (Just "_coQuoteEscapeCharacter") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_coFieldDelimiter") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))))

csvOutput :: CSVOutput Source #

Creates a value of CSVOutput with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

coQuoteCharacter :: Lens' CSVOutput (Maybe Text) Source #

Value used for escaping where the field delimiter is part of the value.

coQuoteFields :: Lens' CSVOutput (Maybe QuoteFields) Source #

Indicates whether or not all output fields should be quoted.

coRecordDelimiter :: Lens' CSVOutput (Maybe Text) Source #

Value used to separate individual records.

coQuoteEscapeCharacter :: Lens' CSVOutput (Maybe Text) Source #

Single character used for escaping the quote character inside an already escaped value.

coFieldDelimiter :: Lens' CSVOutput (Maybe Text) Source #

Value used to separate individual fields in a record.

CommonPrefix

data CommonPrefix Source #

See: commonPrefix smart constructor.

Instances
Eq CommonPrefix Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Data CommonPrefix Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CommonPrefix -> c CommonPrefix #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CommonPrefix #

toConstr :: CommonPrefix -> Constr #

dataTypeOf :: CommonPrefix -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c CommonPrefix) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CommonPrefix) #

gmapT :: (forall b. Data b => b -> b) -> CommonPrefix -> CommonPrefix #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CommonPrefix -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CommonPrefix -> r #

gmapQ :: (forall d. Data d => d -> u) -> CommonPrefix -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CommonPrefix -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CommonPrefix -> m CommonPrefix #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CommonPrefix -> m CommonPrefix #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CommonPrefix -> m CommonPrefix #

Read CommonPrefix Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Show CommonPrefix Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Generic CommonPrefix Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Associated Types

type Rep CommonPrefix :: Type -> Type #

Hashable CommonPrefix Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

FromXML CommonPrefix Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

NFData CommonPrefix Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

rnf :: CommonPrefix -> () #

type Rep CommonPrefix Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

type Rep CommonPrefix = D1 (MetaData "CommonPrefix" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" True) (C1 (MetaCons "CommonPrefix'" PrefixI True) (S1 (MetaSel (Just "_cpPrefix") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Text))))

commonPrefix :: CommonPrefix Source #

Creates a value of CommonPrefix with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

cpPrefix :: Lens' CommonPrefix (Maybe Text) Source #

Undocumented member.

CompletedMultipartUpload

data CompletedMultipartUpload Source #

See: completedMultipartUpload smart constructor.

Instances
Eq CompletedMultipartUpload Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Data CompletedMultipartUpload Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CompletedMultipartUpload -> c CompletedMultipartUpload #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CompletedMultipartUpload #

toConstr :: CompletedMultipartUpload -> Constr #

dataTypeOf :: CompletedMultipartUpload -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c CompletedMultipartUpload) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CompletedMultipartUpload) #

gmapT :: (forall b. Data b => b -> b) -> CompletedMultipartUpload -> CompletedMultipartUpload #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CompletedMultipartUpload -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CompletedMultipartUpload -> r #

gmapQ :: (forall d. Data d => d -> u) -> CompletedMultipartUpload -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CompletedMultipartUpload -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CompletedMultipartUpload -> m CompletedMultipartUpload #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CompletedMultipartUpload -> m CompletedMultipartUpload #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CompletedMultipartUpload -> m CompletedMultipartUpload #

Read CompletedMultipartUpload Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Show CompletedMultipartUpload Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Generic CompletedMultipartUpload Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Associated Types

type Rep CompletedMultipartUpload :: Type -> Type #

Hashable CompletedMultipartUpload Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

ToXML CompletedMultipartUpload Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

NFData CompletedMultipartUpload Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

type Rep CompletedMultipartUpload Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

type Rep CompletedMultipartUpload = D1 (MetaData "CompletedMultipartUpload" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" True) (C1 (MetaCons "CompletedMultipartUpload'" PrefixI True) (S1 (MetaSel (Just "_cmuParts") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (List1 CompletedPart)))))

completedMultipartUpload :: CompletedMultipartUpload Source #

Creates a value of CompletedMultipartUpload with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

CompletedPart

data CompletedPart Source #

See: completedPart smart constructor.

Instances
Eq CompletedPart Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Data CompletedPart Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CompletedPart -> c CompletedPart #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CompletedPart #

toConstr :: CompletedPart -> Constr #

dataTypeOf :: CompletedPart -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c CompletedPart) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CompletedPart) #

gmapT :: (forall b. Data b => b -> b) -> CompletedPart -> CompletedPart #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CompletedPart -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CompletedPart -> r #

gmapQ :: (forall d. Data d => d -> u) -> CompletedPart -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CompletedPart -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CompletedPart -> m CompletedPart #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CompletedPart -> m CompletedPart #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CompletedPart -> m CompletedPart #

Read CompletedPart Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Show CompletedPart Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Generic CompletedPart Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Associated Types

type Rep CompletedPart :: Type -> Type #

Hashable CompletedPart Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

ToXML CompletedPart Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

toXML :: CompletedPart -> XML #

NFData CompletedPart Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

rnf :: CompletedPart -> () #

type Rep CompletedPart Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

type Rep CompletedPart = D1 (MetaData "CompletedPart" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" False) (C1 (MetaCons "CompletedPart'" PrefixI True) (S1 (MetaSel (Just "_cpPartNumber") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int) :*: S1 (MetaSel (Just "_cpETag") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 ETag)))

completedPart Source #

Creates a value of CompletedPart with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • cpPartNumber - Part number that identifies the part. This is a positive integer between 1 and 10,000.
  • cpETag - Entity tag returned when the part was uploaded.

cpPartNumber :: Lens' CompletedPart Int Source #

Part number that identifies the part. This is a positive integer between 1 and 10,000.

cpETag :: Lens' CompletedPart ETag Source #

Entity tag returned when the part was uploaded.

Condition

data Condition Source #

See: condition smart constructor.

Instances
Eq Condition Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Data Condition Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Condition -> c Condition #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Condition #

toConstr :: Condition -> Constr #

dataTypeOf :: Condition -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Condition) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Condition) #

gmapT :: (forall b. Data b => b -> b) -> Condition -> Condition #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Condition -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Condition -> r #

gmapQ :: (forall d. Data d => d -> u) -> Condition -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Condition -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Condition -> m Condition #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Condition -> m Condition #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Condition -> m Condition #

Read Condition Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Show Condition Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Generic Condition Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Associated Types

type Rep Condition :: Type -> Type #

Hashable Condition Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

FromXML Condition Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

ToXML Condition Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

toXML :: Condition -> XML #

NFData Condition Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

rnf :: Condition -> () #

type Rep Condition Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

type Rep Condition = D1 (MetaData "Condition" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" False) (C1 (MetaCons "Condition'" PrefixI True) (S1 (MetaSel (Just "_cKeyPrefixEquals") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_cHTTPErrorCodeReturnedEquals") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))

condition :: Condition Source #

Creates a value of Condition with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • cKeyPrefixEquals - The object key name prefix when the redirect is applied. For example, to redirect requests for ExamplePage.html, the key prefix will be ExamplePage.html. To redirect request for all pages with the prefix docs, the key prefix will be docs, which identifies all objects in the docs/ folder. Required when the parent element Condition is specified and sibling HttpErrorCodeReturnedEquals is not specified. If both conditions are specified, both must be true for the redirect to be applied.
  • cHTTPErrorCodeReturnedEquals - The HTTP error code when the redirect is applied. In the event of an error, if the error code equals this value, then the specified redirect is applied. Required when parent element Condition is specified and sibling KeyPrefixEquals is not specified. If both are specified, then both must be true for the redirect to be applied.

cKeyPrefixEquals :: Lens' Condition (Maybe Text) Source #

The object key name prefix when the redirect is applied. For example, to redirect requests for ExamplePage.html, the key prefix will be ExamplePage.html. To redirect request for all pages with the prefix docs, the key prefix will be docs, which identifies all objects in the docs/ folder. Required when the parent element Condition is specified and sibling HttpErrorCodeReturnedEquals is not specified. If both conditions are specified, both must be true for the redirect to be applied.

cHTTPErrorCodeReturnedEquals :: Lens' Condition (Maybe Text) Source #

The HTTP error code when the redirect is applied. In the event of an error, if the error code equals this value, then the specified redirect is applied. Required when parent element Condition is specified and sibling KeyPrefixEquals is not specified. If both are specified, then both must be true for the redirect to be applied.

ContinuationEvent

data ContinuationEvent Source #

See: continuationEvent smart constructor.

Instances
Eq ContinuationEvent Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Data ContinuationEvent Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ContinuationEvent -> c ContinuationEvent #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ContinuationEvent #

toConstr :: ContinuationEvent -> Constr #

dataTypeOf :: ContinuationEvent -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ContinuationEvent) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ContinuationEvent) #

gmapT :: (forall b. Data b => b -> b) -> ContinuationEvent -> ContinuationEvent #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ContinuationEvent -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ContinuationEvent -> r #

gmapQ :: (forall d. Data d => d -> u) -> ContinuationEvent -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ContinuationEvent -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ContinuationEvent -> m ContinuationEvent #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ContinuationEvent -> m ContinuationEvent #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ContinuationEvent -> m ContinuationEvent #

Read ContinuationEvent Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Show ContinuationEvent Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Generic ContinuationEvent Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Associated Types

type Rep ContinuationEvent :: Type -> Type #

Hashable ContinuationEvent Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

FromXML ContinuationEvent Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

NFData ContinuationEvent Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

rnf :: ContinuationEvent -> () #

type Rep ContinuationEvent Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

type Rep ContinuationEvent = D1 (MetaData "ContinuationEvent" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" False) (C1 (MetaCons "ContinuationEvent'" PrefixI False) (U1 :: Type -> Type))

continuationEvent :: ContinuationEvent Source #

Creates a value of ContinuationEvent with the minimum fields required to make a request.

CopyObjectResult

data CopyObjectResult Source #

See: copyObjectResult smart constructor.

Instances
Eq CopyObjectResult Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Data CopyObjectResult Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CopyObjectResult -> c CopyObjectResult #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CopyObjectResult #

toConstr :: CopyObjectResult -> Constr #

dataTypeOf :: CopyObjectResult -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c CopyObjectResult) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CopyObjectResult) #

gmapT :: (forall b. Data b => b -> b) -> CopyObjectResult -> CopyObjectResult #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CopyObjectResult -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CopyObjectResult -> r #

gmapQ :: (forall d. Data d => d -> u) -> CopyObjectResult -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CopyObjectResult -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CopyObjectResult -> m CopyObjectResult #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CopyObjectResult -> m CopyObjectResult #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CopyObjectResult -> m CopyObjectResult #

Read CopyObjectResult Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Show CopyObjectResult Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Generic CopyObjectResult Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Associated Types

type Rep CopyObjectResult :: Type -> Type #

Hashable CopyObjectResult Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

FromXML CopyObjectResult Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

NFData CopyObjectResult Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

rnf :: CopyObjectResult -> () #

type Rep CopyObjectResult Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

type Rep CopyObjectResult = D1 (MetaData "CopyObjectResult" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" False) (C1 (MetaCons "CopyObjectResult'" PrefixI True) (S1 (MetaSel (Just "_corETag") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ETag)) :*: S1 (MetaSel (Just "_corLastModified") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe RFC822))))

copyObjectResult :: CopyObjectResult Source #

Creates a value of CopyObjectResult with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

corETag :: Lens' CopyObjectResult (Maybe ETag) Source #

Undocumented member.

CopyPartResult

data CopyPartResult Source #

See: copyPartResult smart constructor.

Instances
Eq CopyPartResult Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Data CopyPartResult Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CopyPartResult -> c CopyPartResult #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CopyPartResult #

toConstr :: CopyPartResult -> Constr #

dataTypeOf :: CopyPartResult -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c CopyPartResult) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CopyPartResult) #

gmapT :: (forall b. Data b => b -> b) -> CopyPartResult -> CopyPartResult #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CopyPartResult -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CopyPartResult -> r #

gmapQ :: (forall d. Data d => d -> u) -> CopyPartResult -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CopyPartResult -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CopyPartResult -> m CopyPartResult #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CopyPartResult -> m CopyPartResult #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CopyPartResult -> m CopyPartResult #

Read CopyPartResult Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Show CopyPartResult Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Generic CopyPartResult Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Associated Types

type Rep CopyPartResult :: Type -> Type #

Hashable CopyPartResult Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

FromXML CopyPartResult Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

NFData CopyPartResult Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

rnf :: CopyPartResult -> () #

type Rep CopyPartResult Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

type Rep CopyPartResult = D1 (MetaData "CopyPartResult" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" False) (C1 (MetaCons "CopyPartResult'" PrefixI True) (S1 (MetaSel (Just "_cprETag") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ETag)) :*: S1 (MetaSel (Just "_cprLastModified") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe RFC822))))

copyPartResult :: CopyPartResult Source #

Creates a value of CopyPartResult with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

cprETag :: Lens' CopyPartResult (Maybe ETag) Source #

Entity tag of the object.

cprLastModified :: Lens' CopyPartResult (Maybe UTCTime) Source #

Date and time at which the object was uploaded.

CreateBucketConfiguration

data CreateBucketConfiguration Source #

See: createBucketConfiguration smart constructor.

Instances
Eq CreateBucketConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Data CreateBucketConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CreateBucketConfiguration -> c CreateBucketConfiguration #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CreateBucketConfiguration #

toConstr :: CreateBucketConfiguration -> Constr #

dataTypeOf :: CreateBucketConfiguration -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c CreateBucketConfiguration) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CreateBucketConfiguration) #

gmapT :: (forall b. Data b => b -> b) -> CreateBucketConfiguration -> CreateBucketConfiguration #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CreateBucketConfiguration -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CreateBucketConfiguration -> r #

gmapQ :: (forall d. Data d => d -> u) -> CreateBucketConfiguration -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CreateBucketConfiguration -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CreateBucketConfiguration -> m CreateBucketConfiguration #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CreateBucketConfiguration -> m CreateBucketConfiguration #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CreateBucketConfiguration -> m CreateBucketConfiguration #

Read CreateBucketConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Show CreateBucketConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Generic CreateBucketConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Associated Types

type Rep CreateBucketConfiguration :: Type -> Type #

Hashable CreateBucketConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

ToXML CreateBucketConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

NFData CreateBucketConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

type Rep CreateBucketConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

type Rep CreateBucketConfiguration = D1 (MetaData "CreateBucketConfiguration" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" True) (C1 (MetaCons "CreateBucketConfiguration'" PrefixI True) (S1 (MetaSel (Just "_cbcLocationConstraint") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe LocationConstraint))))

createBucketConfiguration :: CreateBucketConfiguration Source #

Creates a value of CreateBucketConfiguration with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • cbcLocationConstraint - Specifies the region where the bucket will be created. If you don't specify a region, the bucket will be created in US Standard.

cbcLocationConstraint :: Lens' CreateBucketConfiguration (Maybe LocationConstraint) Source #

Specifies the region where the bucket will be created. If you don't specify a region, the bucket will be created in US Standard.

Delete

data Delete Source #

See: delete' smart constructor.

Instances
Eq Delete Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

(==) :: Delete -> Delete -> Bool #

(/=) :: Delete -> Delete -> Bool #

Data Delete Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Delete -> c Delete #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Delete #

toConstr :: Delete -> Constr #

dataTypeOf :: Delete -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Delete) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Delete) #

gmapT :: (forall b. Data b => b -> b) -> Delete -> Delete #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Delete -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Delete -> r #

gmapQ :: (forall d. Data d => d -> u) -> Delete -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Delete -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Delete -> m Delete #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Delete -> m Delete #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Delete -> m Delete #

Read Delete Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Show Delete Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Generic Delete Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Associated Types

type Rep Delete :: Type -> Type #

Methods

from :: Delete -> Rep Delete x #

to :: Rep Delete x -> Delete #

Hashable Delete Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

hashWithSalt :: Int -> Delete -> Int #

hash :: Delete -> Int #

ToXML Delete Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

toXML :: Delete -> XML #

NFData Delete Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

rnf :: Delete -> () #

type Rep Delete Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

type Rep Delete = D1 (MetaData "Delete" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" False) (C1 (MetaCons "Delete'" PrefixI True) (S1 (MetaSel (Just "_dQuiet") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool)) :*: S1 (MetaSel (Just "_dObjects") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [ObjectIdentifier])))

delete' :: Delete Source #

Creates a value of Delete with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • dQuiet - Element to enable quiet mode for the request. When you add this element, you must set its value to true.
  • dObjects - Undocumented member.

dQuiet :: Lens' Delete (Maybe Bool) Source #

Element to enable quiet mode for the request. When you add this element, you must set its value to true.

dObjects :: Lens' Delete [ObjectIdentifier] Source #

Undocumented member.

DeleteMarkerEntry

data DeleteMarkerEntry Source #

See: deleteMarkerEntry smart constructor.

Instances
Eq DeleteMarkerEntry Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Data DeleteMarkerEntry Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DeleteMarkerEntry -> c DeleteMarkerEntry #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DeleteMarkerEntry #

toConstr :: DeleteMarkerEntry -> Constr #

dataTypeOf :: DeleteMarkerEntry -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c DeleteMarkerEntry) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DeleteMarkerEntry) #

gmapT :: (forall b. Data b => b -> b) -> DeleteMarkerEntry -> DeleteMarkerEntry #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DeleteMarkerEntry -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DeleteMarkerEntry -> r #

gmapQ :: (forall d. Data d => d -> u) -> DeleteMarkerEntry -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DeleteMarkerEntry -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DeleteMarkerEntry -> m DeleteMarkerEntry #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DeleteMarkerEntry -> m DeleteMarkerEntry #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DeleteMarkerEntry -> m DeleteMarkerEntry #

Read DeleteMarkerEntry Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Show DeleteMarkerEntry Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Generic DeleteMarkerEntry Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Associated Types

type Rep DeleteMarkerEntry :: Type -> Type #

Hashable DeleteMarkerEntry Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

FromXML DeleteMarkerEntry Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

NFData DeleteMarkerEntry Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

rnf :: DeleteMarkerEntry -> () #

type Rep DeleteMarkerEntry Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

type Rep DeleteMarkerEntry = D1 (MetaData "DeleteMarkerEntry" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" False) (C1 (MetaCons "DeleteMarkerEntry'" PrefixI True) ((S1 (MetaSel (Just "_dmeVersionId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ObjectVersionId)) :*: S1 (MetaSel (Just "_dmeIsLatest") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) :*: (S1 (MetaSel (Just "_dmeOwner") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Owner)) :*: (S1 (MetaSel (Just "_dmeKey") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ObjectKey)) :*: S1 (MetaSel (Just "_dmeLastModified") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe RFC822))))))

deleteMarkerEntry :: DeleteMarkerEntry Source #

Creates a value of DeleteMarkerEntry with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

dmeIsLatest :: Lens' DeleteMarkerEntry (Maybe Bool) Source #

Specifies whether the object is (true) or is not (false) the latest version of an object.

dmeLastModified :: Lens' DeleteMarkerEntry (Maybe UTCTime) Source #

Date and time the object was last modified.

DeletedObject

data DeletedObject Source #

See: deletedObject smart constructor.

Instances
Eq DeletedObject Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Data DeletedObject Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DeletedObject -> c DeletedObject #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DeletedObject #

toConstr :: DeletedObject -> Constr #

dataTypeOf :: DeletedObject -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c DeletedObject) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DeletedObject) #

gmapT :: (forall b. Data b => b -> b) -> DeletedObject -> DeletedObject #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DeletedObject -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DeletedObject -> r #

gmapQ :: (forall d. Data d => d -> u) -> DeletedObject -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DeletedObject -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DeletedObject -> m DeletedObject #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DeletedObject -> m DeletedObject #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DeletedObject -> m DeletedObject #

Read DeletedObject Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Show DeletedObject Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Generic DeletedObject Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Associated Types

type Rep DeletedObject :: Type -> Type #

Hashable DeletedObject Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

FromXML DeletedObject Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

NFData DeletedObject Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

rnf :: DeletedObject -> () #

type Rep DeletedObject Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

type Rep DeletedObject = D1 (MetaData "DeletedObject" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" False) (C1 (MetaCons "DeletedObject'" PrefixI True) ((S1 (MetaSel (Just "_dVersionId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ObjectVersionId)) :*: S1 (MetaSel (Just "_dDeleteMarker") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) :*: (S1 (MetaSel (Just "_dDeleteMarkerVersionId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_dKey") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ObjectKey)))))

deletedObject :: DeletedObject Source #

Creates a value of DeletedObject with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

dKey :: Lens' DeletedObject (Maybe ObjectKey) Source #

Undocumented member.

Destination

data Destination Source #

Container for replication destination information.

See: destination smart constructor.

Instances
Eq Destination Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Data Destination Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Destination -> c Destination #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Destination #

toConstr :: Destination -> Constr #

dataTypeOf :: Destination -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Destination) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Destination) #

gmapT :: (forall b. Data b => b -> b) -> Destination -> Destination #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Destination -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Destination -> r #

gmapQ :: (forall d. Data d => d -> u) -> Destination -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Destination -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Destination -> m Destination #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Destination -> m Destination #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Destination -> m Destination #

Read Destination Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Show Destination Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Generic Destination Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Associated Types

type Rep Destination :: Type -> Type #

Hashable Destination Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

FromXML Destination Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

ToXML Destination Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

toXML :: Destination -> XML #

NFData Destination Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

rnf :: Destination -> () #

type Rep Destination Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

type Rep Destination = D1 (MetaData "Destination" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" False) (C1 (MetaCons "Destination'" PrefixI True) ((S1 (MetaSel (Just "_dAccessControlTranslation") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe AccessControlTranslation)) :*: S1 (MetaSel (Just "_dAccount") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) :*: (S1 (MetaSel (Just "_dStorageClass") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe StorageClass)) :*: (S1 (MetaSel (Just "_dEncryptionConfiguration") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe EncryptionConfiguration)) :*: S1 (MetaSel (Just "_dBucket") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 BucketName)))))

destination Source #

Creates a value of Destination with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • dAccessControlTranslation - Container for information regarding the access control for replicas.
  • dAccount - Account ID of the destination bucket. Currently this is only being verified if Access Control Translation is enabled
  • dStorageClass - The class of storage used to store the object.
  • dEncryptionConfiguration - Container for information regarding encryption based configuration for replicas.
  • dBucket - Amazon resource name (ARN) of the bucket where you want Amazon S3 to store replicas of the object identified by the rule.

dAccessControlTranslation :: Lens' Destination (Maybe AccessControlTranslation) Source #

Container for information regarding the access control for replicas.

dAccount :: Lens' Destination (Maybe Text) Source #

Account ID of the destination bucket. Currently this is only being verified if Access Control Translation is enabled

dStorageClass :: Lens' Destination (Maybe StorageClass) Source #

The class of storage used to store the object.

dEncryptionConfiguration :: Lens' Destination (Maybe EncryptionConfiguration) Source #

Container for information regarding encryption based configuration for replicas.

dBucket :: Lens' Destination BucketName Source #

Amazon resource name (ARN) of the bucket where you want Amazon S3 to store replicas of the object identified by the rule.

Encryption

data Encryption Source #

Describes the server-side encryption that will be applied to the restore results.

See: encryption smart constructor.

Instances
Eq Encryption Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Data Encryption Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Encryption -> c Encryption #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Encryption #

toConstr :: Encryption -> Constr #

dataTypeOf :: Encryption -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Encryption) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Encryption) #

gmapT :: (forall b. Data b => b -> b) -> Encryption -> Encryption #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Encryption -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Encryption -> r #

gmapQ :: (forall d. Data d => d -> u) -> Encryption -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Encryption -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Encryption -> m Encryption #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Encryption -> m Encryption #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Encryption -> m Encryption #

Show Encryption Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Generic Encryption Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Associated Types

type Rep Encryption :: Type -> Type #

Hashable Encryption Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

ToXML Encryption Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

toXML :: Encryption -> XML #

NFData Encryption Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

rnf :: Encryption -> () #

type Rep Encryption Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

type Rep Encryption = D1 (MetaData "Encryption" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" False) (C1 (MetaCons "Encryption'" PrefixI True) (S1 (MetaSel (Just "_eKMSKeyId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Sensitive Text))) :*: (S1 (MetaSel (Just "_eKMSContext") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_eEncryptionType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 ServerSideEncryption))))

encryption Source #

Creates a value of Encryption with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • eKMSKeyId - If the encryption type is aws:kms, this optional value specifies the AWS KMS key ID to use for encryption of job results.
  • eKMSContext - If the encryption type is aws:kms, this optional value can be used to specify the encryption context for the restore results.
  • eEncryptionType - The server-side encryption algorithm used when storing job results in Amazon S3 (e.g., AES256, aws:kms).

eKMSKeyId :: Lens' Encryption (Maybe Text) Source #

If the encryption type is aws:kms, this optional value specifies the AWS KMS key ID to use for encryption of job results.

eKMSContext :: Lens' Encryption (Maybe Text) Source #

If the encryption type is aws:kms, this optional value can be used to specify the encryption context for the restore results.

eEncryptionType :: Lens' Encryption ServerSideEncryption Source #

The server-side encryption algorithm used when storing job results in Amazon S3 (e.g., AES256, aws:kms).

EncryptionConfiguration

data EncryptionConfiguration Source #

Container for information regarding encryption based configuration for replicas.

See: encryptionConfiguration smart constructor.

Instances
Eq EncryptionConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Data EncryptionConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> EncryptionConfiguration -> c EncryptionConfiguration #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c EncryptionConfiguration #

toConstr :: EncryptionConfiguration -> Constr #

dataTypeOf :: EncryptionConfiguration -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c EncryptionConfiguration) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c EncryptionConfiguration) #

gmapT :: (forall b. Data b => b -> b) -> EncryptionConfiguration -> EncryptionConfiguration #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> EncryptionConfiguration -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> EncryptionConfiguration -> r #

gmapQ :: (forall d. Data d => d -> u) -> EncryptionConfiguration -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> EncryptionConfiguration -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> EncryptionConfiguration -> m EncryptionConfiguration #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> EncryptionConfiguration -> m EncryptionConfiguration #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> EncryptionConfiguration -> m EncryptionConfiguration #

Read EncryptionConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Show EncryptionConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Generic EncryptionConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Associated Types

type Rep EncryptionConfiguration :: Type -> Type #

Hashable EncryptionConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

FromXML EncryptionConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

ToXML EncryptionConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

NFData EncryptionConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

rnf :: EncryptionConfiguration -> () #

type Rep EncryptionConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

type Rep EncryptionConfiguration = D1 (MetaData "EncryptionConfiguration" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" True) (C1 (MetaCons "EncryptionConfiguration'" PrefixI True) (S1 (MetaSel (Just "_ecReplicaKMSKeyId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Text))))

encryptionConfiguration :: EncryptionConfiguration Source #

Creates a value of EncryptionConfiguration with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

ecReplicaKMSKeyId :: Lens' EncryptionConfiguration (Maybe Text) Source #

The id of the KMS key used to encrypt the replica object.

EndEvent

data EndEvent Source #

See: endEvent smart constructor.

Instances
Eq EndEvent Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Data EndEvent Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> EndEvent -> c EndEvent #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c EndEvent #

toConstr :: EndEvent -> Constr #

dataTypeOf :: EndEvent -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c EndEvent) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c EndEvent) #

gmapT :: (forall b. Data b => b -> b) -> EndEvent -> EndEvent #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> EndEvent -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> EndEvent -> r #

gmapQ :: (forall d. Data d => d -> u) -> EndEvent -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> EndEvent -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> EndEvent -> m EndEvent #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> EndEvent -> m EndEvent #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> EndEvent -> m EndEvent #

Read EndEvent Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Show EndEvent Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Generic EndEvent Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Associated Types

type Rep EndEvent :: Type -> Type #

Methods

from :: EndEvent -> Rep EndEvent x #

to :: Rep EndEvent x -> EndEvent #

Hashable EndEvent Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

hashWithSalt :: Int -> EndEvent -> Int #

hash :: EndEvent -> Int #

FromXML EndEvent Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

NFData EndEvent Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

rnf :: EndEvent -> () #

type Rep EndEvent Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

type Rep EndEvent = D1 (MetaData "EndEvent" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" False) (C1 (MetaCons "EndEvent'" PrefixI False) (U1 :: Type -> Type))

endEvent :: EndEvent Source #

Creates a value of EndEvent with the minimum fields required to make a request.

ErrorDocument

data ErrorDocument Source #

See: errorDocument smart constructor.

Instances
Eq ErrorDocument Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Data ErrorDocument Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ErrorDocument -> c ErrorDocument #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ErrorDocument #

toConstr :: ErrorDocument -> Constr #

dataTypeOf :: ErrorDocument -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ErrorDocument) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ErrorDocument) #

gmapT :: (forall b. Data b => b -> b) -> ErrorDocument -> ErrorDocument #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ErrorDocument -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ErrorDocument -> r #

gmapQ :: (forall d. Data d => d -> u) -> ErrorDocument -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ErrorDocument -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ErrorDocument -> m ErrorDocument #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ErrorDocument -> m ErrorDocument #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ErrorDocument -> m ErrorDocument #

Read ErrorDocument Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Show ErrorDocument Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Generic ErrorDocument Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Associated Types

type Rep ErrorDocument :: Type -> Type #

Hashable ErrorDocument Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

FromXML ErrorDocument Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

ToXML ErrorDocument Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

toXML :: ErrorDocument -> XML #

NFData ErrorDocument Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

rnf :: ErrorDocument -> () #

type Rep ErrorDocument Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

type Rep ErrorDocument = D1 (MetaData "ErrorDocument" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" True) (C1 (MetaCons "ErrorDocument'" PrefixI True) (S1 (MetaSel (Just "_edKey") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ObjectKey)))

errorDocument Source #

Creates a value of ErrorDocument with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • edKey - The object key name to use when a 4XX class error occurs.

edKey :: Lens' ErrorDocument ObjectKey Source #

The object key name to use when a 4XX class error occurs.

FilterRule

data FilterRule Source #

Container for key value pair that defines the criteria for the filter rule.

See: filterRule smart constructor.

Instances
Eq FilterRule Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Data FilterRule Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FilterRule -> c FilterRule #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FilterRule #

toConstr :: FilterRule -> Constr #

dataTypeOf :: FilterRule -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c FilterRule) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FilterRule) #

gmapT :: (forall b. Data b => b -> b) -> FilterRule -> FilterRule #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FilterRule -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FilterRule -> r #

gmapQ :: (forall d. Data d => d -> u) -> FilterRule -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FilterRule -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FilterRule -> m FilterRule #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FilterRule -> m FilterRule #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FilterRule -> m FilterRule #

Read FilterRule Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Show FilterRule Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Generic FilterRule Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Associated Types

type Rep FilterRule :: Type -> Type #

Hashable FilterRule Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

FromXML FilterRule Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

ToXML FilterRule Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

toXML :: FilterRule -> XML #

NFData FilterRule Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

rnf :: FilterRule -> () #

type Rep FilterRule Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

type Rep FilterRule = D1 (MetaData "FilterRule" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" False) (C1 (MetaCons "FilterRule'" PrefixI True) (S1 (MetaSel (Just "_frValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_frName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe FilterRuleName))))

filterRule :: FilterRule Source #

Creates a value of FilterRule with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

frValue :: Lens' FilterRule (Maybe Text) Source #

Undocumented member.

GlacierJobParameters

data GlacierJobParameters Source #

See: glacierJobParameters smart constructor.

Instances
Eq GlacierJobParameters Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Data GlacierJobParameters Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GlacierJobParameters -> c GlacierJobParameters #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c GlacierJobParameters #

toConstr :: GlacierJobParameters -> Constr #

dataTypeOf :: GlacierJobParameters -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c GlacierJobParameters) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c GlacierJobParameters) #

gmapT :: (forall b. Data b => b -> b) -> GlacierJobParameters -> GlacierJobParameters #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GlacierJobParameters -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GlacierJobParameters -> r #

gmapQ :: (forall d. Data d => d -> u) -> GlacierJobParameters -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GlacierJobParameters -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GlacierJobParameters -> m GlacierJobParameters #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GlacierJobParameters -> m GlacierJobParameters #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GlacierJobParameters -> m GlacierJobParameters #

Read GlacierJobParameters Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Show GlacierJobParameters Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Generic GlacierJobParameters Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Associated Types

type Rep GlacierJobParameters :: Type -> Type #

Hashable GlacierJobParameters Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

ToXML GlacierJobParameters Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

NFData GlacierJobParameters Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

rnf :: GlacierJobParameters -> () #

type Rep GlacierJobParameters Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

type Rep GlacierJobParameters = D1 (MetaData "GlacierJobParameters" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" True) (C1 (MetaCons "GlacierJobParameters'" PrefixI True) (S1 (MetaSel (Just "_gjpTier") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Tier)))

glacierJobParameters Source #

Creates a value of GlacierJobParameters with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • gjpTier - Glacier retrieval tier at which the restore will be processed.

gjpTier :: Lens' GlacierJobParameters Tier Source #

Glacier retrieval tier at which the restore will be processed.

Grant

data Grant Source #

See: grant smart constructor.

Instances
Eq Grant Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

(==) :: Grant -> Grant -> Bool #

(/=) :: Grant -> Grant -> Bool #

Data Grant Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Grant -> c Grant #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Grant #

toConstr :: Grant -> Constr #

dataTypeOf :: Grant -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Grant) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Grant) #

gmapT :: (forall b. Data b => b -> b) -> Grant -> Grant #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Grant -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Grant -> r #

gmapQ :: (forall d. Data d => d -> u) -> Grant -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Grant -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Grant -> m Grant #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Grant -> m Grant #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Grant -> m Grant #

Read Grant Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Show Grant Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

showsPrec :: Int -> Grant -> ShowS #

show :: Grant -> String #

showList :: [Grant] -> ShowS #

Generic Grant Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Associated Types

type Rep Grant :: Type -> Type #

Methods

from :: Grant -> Rep Grant x #

to :: Rep Grant x -> Grant #

Hashable Grant Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

hashWithSalt :: Int -> Grant -> Int #

hash :: Grant -> Int #

FromXML Grant Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

parseXML :: [Node] -> Either String Grant #

ToXML Grant Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

toXML :: Grant -> XML #

NFData Grant Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

rnf :: Grant -> () #

type Rep Grant Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

type Rep Grant = D1 (MetaData "Grant" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" False) (C1 (MetaCons "Grant'" PrefixI True) (S1 (MetaSel (Just "_gPermission") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Permission)) :*: S1 (MetaSel (Just "_gGrantee") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Grantee))))

grant :: Grant Source #

Creates a value of Grant with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

gPermission :: Lens' Grant (Maybe Permission) Source #

Specifies the permission given to the grantee.

gGrantee :: Lens' Grant (Maybe Grantee) Source #

Undocumented member.

Grantee

data Grantee Source #

See: grantee smart constructor.

Instances
Eq Grantee Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

(==) :: Grantee -> Grantee -> Bool #

(/=) :: Grantee -> Grantee -> Bool #

Data Grantee Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Grantee -> c Grantee #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Grantee #

toConstr :: Grantee -> Constr #

dataTypeOf :: Grantee -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Grantee) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Grantee) #

gmapT :: (forall b. Data b => b -> b) -> Grantee -> Grantee #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Grantee -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Grantee -> r #

gmapQ :: (forall d. Data d => d -> u) -> Grantee -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Grantee -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Grantee -> m Grantee #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Grantee -> m Grantee #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Grantee -> m Grantee #

Read Grantee Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Show Grantee Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Generic Grantee Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Associated Types

type Rep Grantee :: Type -> Type #

Methods

from :: Grantee -> Rep Grantee x #

to :: Rep Grantee x -> Grantee #

Hashable Grantee Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

hashWithSalt :: Int -> Grantee -> Int #

hash :: Grantee -> Int #

FromXML Grantee Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

ToXML Grantee Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

toXML :: Grantee -> XML #

NFData Grantee Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

rnf :: Grantee -> () #

type Rep Grantee Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

grantee Source #

Arguments

:: Type

gType

-> Grantee 

Creates a value of Grantee with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • gURI - URI of the grantee group.
  • gEmailAddress - Email address of the grantee.
  • gDisplayName - Screen name of the grantee.
  • gId - The canonical user ID of the grantee.
  • gType - Type of grantee

gURI :: Lens' Grantee (Maybe Text) Source #

URI of the grantee group.

gEmailAddress :: Lens' Grantee (Maybe Text) Source #

Email address of the grantee.

gDisplayName :: Lens' Grantee (Maybe Text) Source #

Screen name of the grantee.

gId :: Lens' Grantee (Maybe Text) Source #

The canonical user ID of the grantee.

gType :: Lens' Grantee Type Source #

Type of grantee

IndexDocument

data IndexDocument Source #

See: indexDocument smart constructor.

Instances
Eq IndexDocument Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Data IndexDocument Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> IndexDocument -> c IndexDocument #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c IndexDocument #

toConstr :: IndexDocument -> Constr #

dataTypeOf :: IndexDocument -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c IndexDocument) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c IndexDocument) #

gmapT :: (forall b. Data b => b -> b) -> IndexDocument -> IndexDocument #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> IndexDocument -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> IndexDocument -> r #

gmapQ :: (forall d. Data d => d -> u) -> IndexDocument -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> IndexDocument -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> IndexDocument -> m IndexDocument #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> IndexDocument -> m IndexDocument #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> IndexDocument -> m IndexDocument #

Read IndexDocument Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Show IndexDocument Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Generic IndexDocument Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Associated Types

type Rep IndexDocument :: Type -> Type #

Hashable IndexDocument Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

FromXML IndexDocument Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

ToXML IndexDocument Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

toXML :: IndexDocument -> XML #

NFData IndexDocument Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

rnf :: IndexDocument -> () #

type Rep IndexDocument Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

type Rep IndexDocument = D1 (MetaData "IndexDocument" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" True) (C1 (MetaCons "IndexDocument'" PrefixI True) (S1 (MetaSel (Just "_idSuffix") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

indexDocument Source #

Arguments

:: Text

idSuffix

-> IndexDocument 

Creates a value of IndexDocument with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • idSuffix - A suffix that is appended to a request that is for a directory on the website endpoint (e.g. if the suffix is index.html and you make a request to samplebucketimages the data that is returned will be for the object with the key name images/index.html) The suffix must not be empty and must not include a slash character.

idSuffix :: Lens' IndexDocument Text Source #

A suffix that is appended to a request that is for a directory on the website endpoint (e.g. if the suffix is index.html and you make a request to samplebucketimages the data that is returned will be for the object with the key name images/index.html) The suffix must not be empty and must not include a slash character.

Initiator

data Initiator Source #

See: initiator smart constructor.

Instances
Eq Initiator Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Data Initiator Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Initiator -> c Initiator #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Initiator #

toConstr :: Initiator -> Constr #

dataTypeOf :: Initiator -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Initiator) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Initiator) #

gmapT :: (forall b. Data b => b -> b) -> Initiator -> Initiator #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Initiator -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Initiator -> r #

gmapQ :: (forall d. Data d => d -> u) -> Initiator -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Initiator -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Initiator -> m Initiator #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Initiator -> m Initiator #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Initiator -> m Initiator #

Read Initiator Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Show Initiator Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Generic Initiator Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Associated Types

type Rep Initiator :: Type -> Type #

Hashable Initiator Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

FromXML Initiator Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

NFData Initiator Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

rnf :: Initiator -> () #

type Rep Initiator Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

type Rep Initiator = D1 (MetaData "Initiator" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" False) (C1 (MetaCons "Initiator'" PrefixI True) (S1 (MetaSel (Just "_iDisplayName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_iId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))

initiator :: Initiator Source #

Creates a value of Initiator with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • iDisplayName - Name of the Principal.
  • iId - If the principal is an AWS account, it provides the Canonical User ID. If the principal is an IAM User, it provides a user ARN value.

iDisplayName :: Lens' Initiator (Maybe Text) Source #

Name of the Principal.

iId :: Lens' Initiator (Maybe Text) Source #

If the principal is an AWS account, it provides the Canonical User ID. If the principal is an IAM User, it provides a user ARN value.

InputSerialization

data InputSerialization Source #

Describes the serialization format of the object.

See: inputSerialization smart constructor.

Instances
Eq InputSerialization Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Data InputSerialization Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> InputSerialization -> c InputSerialization #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c InputSerialization #

toConstr :: InputSerialization -> Constr #

dataTypeOf :: InputSerialization -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c InputSerialization) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c InputSerialization) #

gmapT :: (forall b. Data b => b -> b) -> InputSerialization -> InputSerialization #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> InputSerialization -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> InputSerialization -> r #

gmapQ :: (forall d. Data d => d -> u) -> InputSerialization -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> InputSerialization -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> InputSerialization -> m InputSerialization #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> InputSerialization -> m InputSerialization #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> InputSerialization -> m InputSerialization #

Read InputSerialization Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Show InputSerialization Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Generic InputSerialization Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Associated Types

type Rep InputSerialization :: Type -> Type #

Hashable InputSerialization Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

ToXML InputSerialization Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

NFData InputSerialization Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

rnf :: InputSerialization -> () #

type Rep InputSerialization Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

type Rep InputSerialization = D1 (MetaData "InputSerialization" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" False) (C1 (MetaCons "InputSerialization'" PrefixI True) (S1 (MetaSel (Just "_isJSON") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe JSONInput)) :*: (S1 (MetaSel (Just "_isCSV") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe CSVInput)) :*: S1 (MetaSel (Just "_isCompressionType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe CompressionType)))))

inputSerialization :: InputSerialization Source #

Creates a value of InputSerialization with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • isJSON - Specifies JSON as object's input serialization format.
  • isCSV - Describes the serialization of a CSV-encoded object.
  • isCompressionType - Specifies object's compression format. Valid values: NONE, GZIP. Default Value: NONE.

isJSON :: Lens' InputSerialization (Maybe JSONInput) Source #

Specifies JSON as object's input serialization format.

isCSV :: Lens' InputSerialization (Maybe CSVInput) Source #

Describes the serialization of a CSV-encoded object.

isCompressionType :: Lens' InputSerialization (Maybe CompressionType) Source #

Specifies object's compression format. Valid values: NONE, GZIP. Default Value: NONE.

InventoryConfiguration

data InventoryConfiguration Source #

See: inventoryConfiguration smart constructor.

Instances
Eq InventoryConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Data InventoryConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> InventoryConfiguration -> c InventoryConfiguration #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c InventoryConfiguration #

toConstr :: InventoryConfiguration -> Constr #

dataTypeOf :: InventoryConfiguration -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c InventoryConfiguration) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c InventoryConfiguration) #

gmapT :: (forall b. Data b => b -> b) -> InventoryConfiguration -> InventoryConfiguration #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> InventoryConfiguration -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> InventoryConfiguration -> r #

gmapQ :: (forall d. Data d => d -> u) -> InventoryConfiguration -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> InventoryConfiguration -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> InventoryConfiguration -> m InventoryConfiguration #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> InventoryConfiguration -> m InventoryConfiguration #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> InventoryConfiguration -> m InventoryConfiguration #

Show InventoryConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Generic InventoryConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Associated Types

type Rep InventoryConfiguration :: Type -> Type #

Hashable InventoryConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

FromXML InventoryConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

ToXML InventoryConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

NFData InventoryConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

rnf :: InventoryConfiguration -> () #

type Rep InventoryConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

inventoryConfiguration Source #

Creates a value of InventoryConfiguration with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • icOptionalFields - Contains the optional fields that are included in the inventory results.
  • icFilter - Specifies an inventory filter. The inventory only includes objects that meet the filter's criteria.
  • icDestination - Contains information about where to publish the inventory results.
  • icIsEnabled - Specifies whether the inventory is enabled or disabled.
  • icId - The ID used to identify the inventory configuration.
  • icIncludedObjectVersions - Specifies which object version(s) to included in the inventory results.
  • icSchedule - Specifies the schedule for generating inventory results.

icOptionalFields :: Lens' InventoryConfiguration [InventoryOptionalField] Source #

Contains the optional fields that are included in the inventory results.

icFilter :: Lens' InventoryConfiguration (Maybe InventoryFilter) Source #

Specifies an inventory filter. The inventory only includes objects that meet the filter's criteria.

icDestination :: Lens' InventoryConfiguration InventoryDestination Source #

Contains information about where to publish the inventory results.

icIsEnabled :: Lens' InventoryConfiguration Bool Source #

Specifies whether the inventory is enabled or disabled.

icId :: Lens' InventoryConfiguration Text Source #

The ID used to identify the inventory configuration.

icIncludedObjectVersions :: Lens' InventoryConfiguration InventoryIncludedObjectVersions Source #

Specifies which object version(s) to included in the inventory results.

icSchedule :: Lens' InventoryConfiguration InventorySchedule Source #

Specifies the schedule for generating inventory results.

InventoryDestination

data InventoryDestination Source #

See: inventoryDestination smart constructor.

Instances
Eq InventoryDestination Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Data InventoryDestination Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> InventoryDestination -> c InventoryDestination #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c InventoryDestination #

toConstr :: InventoryDestination -> Constr #

dataTypeOf :: InventoryDestination -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c InventoryDestination) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c InventoryDestination) #

gmapT :: (forall b. Data b => b -> b) -> InventoryDestination -> InventoryDestination #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> InventoryDestination -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> InventoryDestination -> r #

gmapQ :: (forall d. Data d => d -> u) -> InventoryDestination -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> InventoryDestination -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> InventoryDestination -> m InventoryDestination #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> InventoryDestination -> m InventoryDestination #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> InventoryDestination -> m InventoryDestination #

Show InventoryDestination Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Generic InventoryDestination Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Associated Types

type Rep InventoryDestination :: Type -> Type #

Hashable InventoryDestination Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

FromXML InventoryDestination Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

ToXML InventoryDestination Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

NFData InventoryDestination Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

rnf :: InventoryDestination -> () #

type Rep InventoryDestination Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

type Rep InventoryDestination = D1 (MetaData "InventoryDestination" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" True) (C1 (MetaCons "InventoryDestination'" PrefixI True) (S1 (MetaSel (Just "_idS3BucketDestination") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 InventoryS3BucketDestination)))

inventoryDestination Source #

Creates a value of InventoryDestination with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • idS3BucketDestination - Contains the bucket name, file format, bucket owner (optional), and prefix (optional) where inventory results are published.

idS3BucketDestination :: Lens' InventoryDestination InventoryS3BucketDestination Source #

Contains the bucket name, file format, bucket owner (optional), and prefix (optional) where inventory results are published.

InventoryEncryption

data InventoryEncryption Source #

Contains the type of server-side encryption used to encrypt the inventory results.

See: inventoryEncryption smart constructor.

Instances
Eq InventoryEncryption Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Data InventoryEncryption Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> InventoryEncryption -> c InventoryEncryption #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c InventoryEncryption #

toConstr :: InventoryEncryption -> Constr #

dataTypeOf :: InventoryEncryption -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c InventoryEncryption) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c InventoryEncryption) #

gmapT :: (forall b. Data b => b -> b) -> InventoryEncryption -> InventoryEncryption #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> InventoryEncryption -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> InventoryEncryption -> r #

gmapQ :: (forall d. Data d => d -> u) -> InventoryEncryption -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> InventoryEncryption -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> InventoryEncryption -> m InventoryEncryption #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> InventoryEncryption -> m InventoryEncryption #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> InventoryEncryption -> m InventoryEncryption #

Show InventoryEncryption Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Generic InventoryEncryption Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Associated Types

type Rep InventoryEncryption :: Type -> Type #

Hashable InventoryEncryption Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

FromXML InventoryEncryption Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

ToXML InventoryEncryption Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

NFData InventoryEncryption Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

rnf :: InventoryEncryption -> () #

type Rep InventoryEncryption Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

type Rep InventoryEncryption = D1 (MetaData "InventoryEncryption" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" False) (C1 (MetaCons "InventoryEncryption'" PrefixI True) (S1 (MetaSel (Just "_ieSSES3") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe SSES3)) :*: S1 (MetaSel (Just "_ieSSEKMS") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe SSEKMS))))

inventoryEncryption :: InventoryEncryption Source #

Creates a value of InventoryEncryption with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • ieSSES3 - Specifies the use of SSE-S3 to encrypt delievered Inventory reports.
  • ieSSEKMS - Specifies the use of SSE-KMS to encrypt delievered Inventory reports.

ieSSES3 :: Lens' InventoryEncryption (Maybe SSES3) Source #

Specifies the use of SSE-S3 to encrypt delievered Inventory reports.

ieSSEKMS :: Lens' InventoryEncryption (Maybe SSEKMS) Source #

Specifies the use of SSE-KMS to encrypt delievered Inventory reports.

InventoryFilter

data InventoryFilter Source #

See: inventoryFilter smart constructor.

Instances
Eq InventoryFilter Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Data InventoryFilter Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> InventoryFilter -> c InventoryFilter #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c InventoryFilter #

toConstr :: InventoryFilter -> Constr #

dataTypeOf :: InventoryFilter -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c InventoryFilter) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c InventoryFilter) #

gmapT :: (forall b. Data b => b -> b) -> InventoryFilter -> InventoryFilter #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> InventoryFilter -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> InventoryFilter -> r #

gmapQ :: (forall d. Data d => d -> u) -> InventoryFilter -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> InventoryFilter -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> InventoryFilter -> m InventoryFilter #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> InventoryFilter -> m InventoryFilter #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> InventoryFilter -> m InventoryFilter #

Read InventoryFilter Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Show InventoryFilter Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Generic InventoryFilter Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Associated Types

type Rep InventoryFilter :: Type -> Type #

Hashable InventoryFilter Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

FromXML InventoryFilter Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

ToXML InventoryFilter Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

toXML :: InventoryFilter -> XML #

NFData InventoryFilter Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

rnf :: InventoryFilter -> () #

type Rep InventoryFilter Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

type Rep InventoryFilter = D1 (MetaData "InventoryFilter" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" True) (C1 (MetaCons "InventoryFilter'" PrefixI True) (S1 (MetaSel (Just "_ifPrefix") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

inventoryFilter Source #

Creates a value of InventoryFilter with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • ifPrefix - The prefix that an object must have to be included in the inventory results.

ifPrefix :: Lens' InventoryFilter Text Source #

The prefix that an object must have to be included in the inventory results.

InventoryS3BucketDestination

data InventoryS3BucketDestination Source #

See: inventoryS3BucketDestination smart constructor.

Instances
Eq InventoryS3BucketDestination Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Data InventoryS3BucketDestination Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> InventoryS3BucketDestination -> c InventoryS3BucketDestination #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c InventoryS3BucketDestination #

toConstr :: InventoryS3BucketDestination -> Constr #

dataTypeOf :: InventoryS3BucketDestination -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c InventoryS3BucketDestination) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c InventoryS3BucketDestination) #

gmapT :: (forall b. Data b => b -> b) -> InventoryS3BucketDestination -> InventoryS3BucketDestination #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> InventoryS3BucketDestination -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> InventoryS3BucketDestination -> r #

gmapQ :: (forall d. Data d => d -> u) -> InventoryS3BucketDestination -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> InventoryS3BucketDestination -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> InventoryS3BucketDestination -> m InventoryS3BucketDestination #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> InventoryS3BucketDestination -> m InventoryS3BucketDestination #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> InventoryS3BucketDestination -> m InventoryS3BucketDestination #

Show InventoryS3BucketDestination Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Generic InventoryS3BucketDestination Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Associated Types

type Rep InventoryS3BucketDestination :: Type -> Type #

Hashable InventoryS3BucketDestination Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

FromXML InventoryS3BucketDestination Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

ToXML InventoryS3BucketDestination Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

NFData InventoryS3BucketDestination Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

type Rep InventoryS3BucketDestination Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

type Rep InventoryS3BucketDestination = D1 (MetaData "InventoryS3BucketDestination" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" False) (C1 (MetaCons "InventoryS3BucketDestination'" PrefixI True) ((S1 (MetaSel (Just "_isbdPrefix") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_isbdAccountId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) :*: (S1 (MetaSel (Just "_isbdEncryption") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe InventoryEncryption)) :*: (S1 (MetaSel (Just "_isbdBucket") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 BucketName) :*: S1 (MetaSel (Just "_isbdFormat") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 InventoryFormat)))))

inventoryS3BucketDestination Source #

Creates a value of InventoryS3BucketDestination with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • isbdPrefix - The prefix that is prepended to all inventory results.
  • isbdAccountId - The ID of the account that owns the destination bucket.
  • isbdEncryption - Contains the type of server-side encryption used to encrypt the inventory results.
  • isbdBucket - The Amazon resource name (ARN) of the bucket where inventory results will be published.
  • isbdFormat - Specifies the output format of the inventory results.

isbdPrefix :: Lens' InventoryS3BucketDestination (Maybe Text) Source #

The prefix that is prepended to all inventory results.

isbdAccountId :: Lens' InventoryS3BucketDestination (Maybe Text) Source #

The ID of the account that owns the destination bucket.

isbdEncryption :: Lens' InventoryS3BucketDestination (Maybe InventoryEncryption) Source #

Contains the type of server-side encryption used to encrypt the inventory results.

isbdBucket :: Lens' InventoryS3BucketDestination BucketName Source #

The Amazon resource name (ARN) of the bucket where inventory results will be published.

isbdFormat :: Lens' InventoryS3BucketDestination InventoryFormat Source #

Specifies the output format of the inventory results.

InventorySchedule

data InventorySchedule Source #

See: inventorySchedule smart constructor.

Instances
Eq InventorySchedule Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Data InventorySchedule Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> InventorySchedule -> c InventorySchedule #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c InventorySchedule #

toConstr :: InventorySchedule -> Constr #

dataTypeOf :: InventorySchedule -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c InventorySchedule) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c InventorySchedule) #

gmapT :: (forall b. Data b => b -> b) -> InventorySchedule -> InventorySchedule #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> InventorySchedule -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> InventorySchedule -> r #

gmapQ :: (forall d. Data d => d -> u) -> InventorySchedule -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> InventorySchedule -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> InventorySchedule -> m InventorySchedule #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> InventorySchedule -> m InventorySchedule #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> InventorySchedule -> m InventorySchedule #

Read InventorySchedule Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Show InventorySchedule Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Generic InventorySchedule Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Associated Types

type Rep InventorySchedule :: Type -> Type #

Hashable InventorySchedule Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

FromXML InventorySchedule Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

ToXML InventorySchedule Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

NFData InventorySchedule Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

rnf :: InventorySchedule -> () #

type Rep InventorySchedule Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

type Rep InventorySchedule = D1 (MetaData "InventorySchedule" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" True) (C1 (MetaCons "InventorySchedule'" PrefixI True) (S1 (MetaSel (Just "_isFrequency") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 InventoryFrequency)))

inventorySchedule Source #

Creates a value of InventorySchedule with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • isFrequency - Specifies how frequently inventory results are produced.

isFrequency :: Lens' InventorySchedule InventoryFrequency Source #

Specifies how frequently inventory results are produced.

JSONInput

data JSONInput Source #

See: jsonInput smart constructor.

Instances
Eq JSONInput Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Data JSONInput Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> JSONInput -> c JSONInput #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c JSONInput #

toConstr :: JSONInput -> Constr #

dataTypeOf :: JSONInput -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c JSONInput) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c JSONInput) #

gmapT :: (forall b. Data b => b -> b) -> JSONInput -> JSONInput #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> JSONInput -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> JSONInput -> r #

gmapQ :: (forall d. Data d => d -> u) -> JSONInput -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> JSONInput -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> JSONInput -> m JSONInput #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> JSONInput -> m JSONInput #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> JSONInput -> m JSONInput #

Read JSONInput Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Show JSONInput Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Generic JSONInput Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Associated Types

type Rep JSONInput :: Type -> Type #

Hashable JSONInput Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

ToXML JSONInput Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

toXML :: JSONInput -> XML #

NFData JSONInput Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

rnf :: JSONInput -> () #

type Rep JSONInput Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

type Rep JSONInput = D1 (MetaData "JSONInput" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" True) (C1 (MetaCons "JSONInput'" PrefixI True) (S1 (MetaSel (Just "_jiType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe JSONType))))

jsonInput :: JSONInput Source #

Creates a value of JSONInput with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • jiType - The type of JSON. Valid values: Document, Lines.

jiType :: Lens' JSONInput (Maybe JSONType) Source #

The type of JSON. Valid values: Document, Lines.

JSONOutput

data JSONOutput Source #

See: jsonOutput smart constructor.

Instances
Eq JSONOutput Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Data JSONOutput Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> JSONOutput -> c JSONOutput #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c JSONOutput #

toConstr :: JSONOutput -> Constr #

dataTypeOf :: JSONOutput -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c JSONOutput) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c JSONOutput) #

gmapT :: (forall b. Data b => b -> b) -> JSONOutput -> JSONOutput #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> JSONOutput -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> JSONOutput -> r #

gmapQ :: (forall d. Data d => d -> u) -> JSONOutput -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> JSONOutput -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> JSONOutput -> m JSONOutput #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> JSONOutput -> m JSONOutput #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> JSONOutput -> m JSONOutput #

Read JSONOutput Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Show JSONOutput Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Generic JSONOutput Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Associated Types

type Rep JSONOutput :: Type -> Type #

Hashable JSONOutput Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

ToXML JSONOutput Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

toXML :: JSONOutput -> XML #

NFData JSONOutput Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

rnf :: JSONOutput -> () #

type Rep JSONOutput Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

type Rep JSONOutput = D1 (MetaData "JSONOutput" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" True) (C1 (MetaCons "JSONOutput'" PrefixI True) (S1 (MetaSel (Just "_joRecordDelimiter") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Text))))

jsonOutput :: JSONOutput Source #

Creates a value of JSONOutput with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

joRecordDelimiter :: Lens' JSONOutput (Maybe Text) Source #

The value used to separate individual records in the output.

LambdaFunctionConfiguration

data LambdaFunctionConfiguration Source #

Container for specifying the AWS Lambda notification configuration.

See: lambdaFunctionConfiguration smart constructor.

Instances
Eq LambdaFunctionConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Data LambdaFunctionConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LambdaFunctionConfiguration -> c LambdaFunctionConfiguration #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c LambdaFunctionConfiguration #

toConstr :: LambdaFunctionConfiguration -> Constr #

dataTypeOf :: LambdaFunctionConfiguration -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c LambdaFunctionConfiguration) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c LambdaFunctionConfiguration) #

gmapT :: (forall b. Data b => b -> b) -> LambdaFunctionConfiguration -> LambdaFunctionConfiguration #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LambdaFunctionConfiguration -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LambdaFunctionConfiguration -> r #

gmapQ :: (forall d. Data d => d -> u) -> LambdaFunctionConfiguration -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> LambdaFunctionConfiguration -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> LambdaFunctionConfiguration -> m LambdaFunctionConfiguration #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LambdaFunctionConfiguration -> m LambdaFunctionConfiguration #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LambdaFunctionConfiguration -> m LambdaFunctionConfiguration #

Read LambdaFunctionConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Show LambdaFunctionConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Generic LambdaFunctionConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Associated Types

type Rep LambdaFunctionConfiguration :: Type -> Type #

Hashable LambdaFunctionConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

FromXML LambdaFunctionConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

ToXML LambdaFunctionConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

NFData LambdaFunctionConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

type Rep LambdaFunctionConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

type Rep LambdaFunctionConfiguration = D1 (MetaData "LambdaFunctionConfiguration" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" False) (C1 (MetaCons "LambdaFunctionConfiguration'" PrefixI True) ((S1 (MetaSel (Just "_lfcId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_lfcFilter") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe NotificationConfigurationFilter))) :*: (S1 (MetaSel (Just "_lfcLambdaFunctionARN") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text) :*: S1 (MetaSel (Just "_lfcEvents") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [Event]))))

lambdaFunctionConfiguration Source #

Creates a value of LambdaFunctionConfiguration with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

lfcLambdaFunctionARN :: Lens' LambdaFunctionConfiguration Text Source #

Lambda cloud function ARN that Amazon S3 can invoke when it detects events of the specified type.

LifecycleExpiration

data LifecycleExpiration Source #

See: lifecycleExpiration smart constructor.

Instances
Eq LifecycleExpiration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Data LifecycleExpiration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LifecycleExpiration -> c LifecycleExpiration #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c LifecycleExpiration #

toConstr :: LifecycleExpiration -> Constr #

dataTypeOf :: LifecycleExpiration -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c LifecycleExpiration) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c LifecycleExpiration) #

gmapT :: (forall b. Data b => b -> b) -> LifecycleExpiration -> LifecycleExpiration #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LifecycleExpiration -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LifecycleExpiration -> r #

gmapQ :: (forall d. Data d => d -> u) -> LifecycleExpiration -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> LifecycleExpiration -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> LifecycleExpiration -> m LifecycleExpiration #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LifecycleExpiration -> m LifecycleExpiration #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LifecycleExpiration -> m LifecycleExpiration #

Read LifecycleExpiration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Show LifecycleExpiration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Generic LifecycleExpiration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Associated Types

type Rep LifecycleExpiration :: Type -> Type #

Hashable LifecycleExpiration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

FromXML LifecycleExpiration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

ToXML LifecycleExpiration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

NFData LifecycleExpiration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

rnf :: LifecycleExpiration -> () #

type Rep LifecycleExpiration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

type Rep LifecycleExpiration = D1 (MetaData "LifecycleExpiration" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" False) (C1 (MetaCons "LifecycleExpiration'" PrefixI True) (S1 (MetaSel (Just "_leDays") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Int)) :*: (S1 (MetaSel (Just "_leDate") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe RFC822)) :*: S1 (MetaSel (Just "_leExpiredObjectDeleteMarker") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool)))))

lifecycleExpiration :: LifecycleExpiration Source #

Creates a value of LifecycleExpiration with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • leDays - Indicates the lifetime, in days, of the objects that are subject to the rule. The value must be a non-zero positive integer.
  • leDate - Indicates at what date the object is to be moved or deleted. Should be in GMT ISO 8601 Format.
  • leExpiredObjectDeleteMarker - Indicates whether Amazon S3 will remove a delete marker with no noncurrent versions. If set to true, the delete marker will be expired; if set to false the policy takes no action. This cannot be specified with Days or Date in a Lifecycle Expiration Policy.

leDays :: Lens' LifecycleExpiration (Maybe Int) Source #

Indicates the lifetime, in days, of the objects that are subject to the rule. The value must be a non-zero positive integer.

leDate :: Lens' LifecycleExpiration (Maybe UTCTime) Source #

Indicates at what date the object is to be moved or deleted. Should be in GMT ISO 8601 Format.

leExpiredObjectDeleteMarker :: Lens' LifecycleExpiration (Maybe Bool) Source #

Indicates whether Amazon S3 will remove a delete marker with no noncurrent versions. If set to true, the delete marker will be expired; if set to false the policy takes no action. This cannot be specified with Days or Date in a Lifecycle Expiration Policy.

LifecycleRule

data LifecycleRule Source #

See: lifecycleRule smart constructor.

Instances
Eq LifecycleRule Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Data LifecycleRule Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LifecycleRule -> c LifecycleRule #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c LifecycleRule #

toConstr :: LifecycleRule -> Constr #

dataTypeOf :: LifecycleRule -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c LifecycleRule) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c LifecycleRule) #

gmapT :: (forall b. Data b => b -> b) -> LifecycleRule -> LifecycleRule #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LifecycleRule -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LifecycleRule -> r #

gmapQ :: (forall d. Data d => d -> u) -> LifecycleRule -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> LifecycleRule -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> LifecycleRule -> m LifecycleRule #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LifecycleRule -> m LifecycleRule #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LifecycleRule -> m LifecycleRule #

Read LifecycleRule Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Show LifecycleRule Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Generic LifecycleRule Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Associated Types

type Rep LifecycleRule :: Type -> Type #

Hashable LifecycleRule Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

FromXML LifecycleRule Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

ToXML LifecycleRule Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

toXML :: LifecycleRule -> XML #

NFData LifecycleRule Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

rnf :: LifecycleRule -> () #

type Rep LifecycleRule Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

lifecycleRule Source #

Creates a value of LifecycleRule with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

lrPrefix :: Lens' LifecycleRule (Maybe Text) Source #

Prefix identifying one or more objects to which the rule applies. This is deprecated; use Filter instead.

lrId :: Lens' LifecycleRule (Maybe Text) Source #

Unique identifier for the rule. The value cannot be longer than 255 characters.

lrStatus :: Lens' LifecycleRule ExpirationStatus Source #

If Enabled, the rule is currently being applied. If Disabled, the rule is not currently being applied.

LifecycleRuleAndOperator

data LifecycleRuleAndOperator Source #

This is used in a Lifecycle Rule Filter to apply a logical AND to two or more predicates. The Lifecycle Rule will apply to any object matching all of the predicates configured inside the And operator.

See: lifecycleRuleAndOperator smart constructor.

Instances
Eq LifecycleRuleAndOperator Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Data LifecycleRuleAndOperator Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LifecycleRuleAndOperator -> c LifecycleRuleAndOperator #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c LifecycleRuleAndOperator #

toConstr :: LifecycleRuleAndOperator -> Constr #

dataTypeOf :: LifecycleRuleAndOperator -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c LifecycleRuleAndOperator) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c LifecycleRuleAndOperator) #

gmapT :: (forall b. Data b => b -> b) -> LifecycleRuleAndOperator -> LifecycleRuleAndOperator #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LifecycleRuleAndOperator -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LifecycleRuleAndOperator -> r #

gmapQ :: (forall d. Data d => d -> u) -> LifecycleRuleAndOperator -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> LifecycleRuleAndOperator -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> LifecycleRuleAndOperator -> m LifecycleRuleAndOperator #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LifecycleRuleAndOperator -> m LifecycleRuleAndOperator #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LifecycleRuleAndOperator -> m LifecycleRuleAndOperator #

Read LifecycleRuleAndOperator Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Show LifecycleRuleAndOperator Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Generic LifecycleRuleAndOperator Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Associated Types

type Rep LifecycleRuleAndOperator :: Type -> Type #

Hashable LifecycleRuleAndOperator Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

FromXML LifecycleRuleAndOperator Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

ToXML LifecycleRuleAndOperator Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

NFData LifecycleRuleAndOperator Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

type Rep LifecycleRuleAndOperator Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

type Rep LifecycleRuleAndOperator = D1 (MetaData "LifecycleRuleAndOperator" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" False) (C1 (MetaCons "LifecycleRuleAndOperator'" PrefixI True) (S1 (MetaSel (Just "_lraoPrefix") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_lraoTags") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Tag]))))

lifecycleRuleAndOperator :: LifecycleRuleAndOperator Source #

Creates a value of LifecycleRuleAndOperator with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • lraoPrefix - Undocumented member.
  • lraoTags - All of these tags must exist in the object's tag set in order for the rule to apply.

lraoTags :: Lens' LifecycleRuleAndOperator [Tag] Source #

All of these tags must exist in the object's tag set in order for the rule to apply.

LifecycleRuleFilter

data LifecycleRuleFilter Source #

The Filter is used to identify objects that a Lifecycle Rule applies to. A Filter must have exactly one of Prefix, Tag, or And specified.

See: lifecycleRuleFilter smart constructor.

Instances
Eq LifecycleRuleFilter Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Data LifecycleRuleFilter Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LifecycleRuleFilter -> c LifecycleRuleFilter #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c LifecycleRuleFilter #

toConstr :: LifecycleRuleFilter -> Constr #

dataTypeOf :: LifecycleRuleFilter -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c LifecycleRuleFilter) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c LifecycleRuleFilter) #

gmapT :: (forall b. Data b => b -> b) -> LifecycleRuleFilter -> LifecycleRuleFilter #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LifecycleRuleFilter -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LifecycleRuleFilter -> r #

gmapQ :: (forall d. Data d => d -> u) -> LifecycleRuleFilter -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> LifecycleRuleFilter -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> LifecycleRuleFilter -> m LifecycleRuleFilter #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LifecycleRuleFilter -> m LifecycleRuleFilter #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LifecycleRuleFilter -> m LifecycleRuleFilter #

Read LifecycleRuleFilter Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Show LifecycleRuleFilter Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Generic LifecycleRuleFilter Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Associated Types

type Rep LifecycleRuleFilter :: Type -> Type #

Hashable LifecycleRuleFilter Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

FromXML LifecycleRuleFilter Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

ToXML LifecycleRuleFilter Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

NFData LifecycleRuleFilter Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

rnf :: LifecycleRuleFilter -> () #

type Rep LifecycleRuleFilter Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

type Rep LifecycleRuleFilter = D1 (MetaData "LifecycleRuleFilter" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" False) (C1 (MetaCons "LifecycleRuleFilter'" PrefixI True) (S1 (MetaSel (Just "_lrfTag") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Tag)) :*: (S1 (MetaSel (Just "_lrfPrefix") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_lrfAnd") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe LifecycleRuleAndOperator)))))

lifecycleRuleFilter :: LifecycleRuleFilter Source #

Creates a value of LifecycleRuleFilter with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • lrfTag - This tag must exist in the object's tag set in order for the rule to apply.
  • lrfPrefix - Prefix identifying one or more objects to which the rule applies.
  • lrfAnd - Undocumented member.

lrfTag :: Lens' LifecycleRuleFilter (Maybe Tag) Source #

This tag must exist in the object's tag set in order for the rule to apply.

lrfPrefix :: Lens' LifecycleRuleFilter (Maybe Text) Source #

Prefix identifying one or more objects to which the rule applies.

LoggingEnabled

data LoggingEnabled Source #

Container for logging information. Presence of this element indicates that logging is enabled. Parameters TargetBucket and TargetPrefix are required in this case.

See: loggingEnabled smart constructor.

Instances
Eq LoggingEnabled Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Data LoggingEnabled Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LoggingEnabled -> c LoggingEnabled #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c LoggingEnabled #

toConstr :: LoggingEnabled -> Constr #

dataTypeOf :: LoggingEnabled -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c LoggingEnabled) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c LoggingEnabled) #

gmapT :: (forall b. Data b => b -> b) -> LoggingEnabled -> LoggingEnabled #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LoggingEnabled -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LoggingEnabled -> r #

gmapQ :: (forall d. Data d => d -> u) -> LoggingEnabled -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> LoggingEnabled -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> LoggingEnabled -> m LoggingEnabled #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LoggingEnabled -> m LoggingEnabled #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LoggingEnabled -> m LoggingEnabled #

Read LoggingEnabled Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Show LoggingEnabled Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Generic LoggingEnabled Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Associated Types

type Rep LoggingEnabled :: Type -> Type #

Hashable LoggingEnabled Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

FromXML LoggingEnabled Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

ToXML LoggingEnabled Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

toXML :: LoggingEnabled -> XML #

NFData LoggingEnabled Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

rnf :: LoggingEnabled -> () #

type Rep LoggingEnabled Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

type Rep LoggingEnabled = D1 (MetaData "LoggingEnabled" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" False) (C1 (MetaCons "LoggingEnabled'" PrefixI True) (S1 (MetaSel (Just "_leTargetGrants") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [TargetGrant])) :*: (S1 (MetaSel (Just "_leTargetBucket") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text) :*: S1 (MetaSel (Just "_leTargetPrefix") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text))))

loggingEnabled Source #

Creates a value of LoggingEnabled with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • leTargetGrants - Undocumented member.
  • leTargetBucket - Specifies the bucket where you want Amazon S3 to store server access logs. You can have your logs delivered to any bucket that you own, including the same bucket that is being logged. You can also configure multiple buckets to deliver their logs to the same target bucket. In this case you should choose a different TargetPrefix for each source bucket so that the delivered log files can be distinguished by key.
  • leTargetPrefix - This element lets you specify a prefix for the keys that the log files will be stored under.

leTargetBucket :: Lens' LoggingEnabled Text Source #

Specifies the bucket where you want Amazon S3 to store server access logs. You can have your logs delivered to any bucket that you own, including the same bucket that is being logged. You can also configure multiple buckets to deliver their logs to the same target bucket. In this case you should choose a different TargetPrefix for each source bucket so that the delivered log files can be distinguished by key.

leTargetPrefix :: Lens' LoggingEnabled Text Source #

This element lets you specify a prefix for the keys that the log files will be stored under.

MetadataEntry

data MetadataEntry Source #

A metadata key-value pair to store with an object.

See: metadataEntry smart constructor.

Instances
Eq MetadataEntry Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Data MetadataEntry Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MetadataEntry -> c MetadataEntry #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c MetadataEntry #

toConstr :: MetadataEntry -> Constr #

dataTypeOf :: MetadataEntry -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c MetadataEntry) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MetadataEntry) #

gmapT :: (forall b. Data b => b -> b) -> MetadataEntry -> MetadataEntry #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MetadataEntry -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MetadataEntry -> r #

gmapQ :: (forall d. Data d => d -> u) -> MetadataEntry -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MetadataEntry -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MetadataEntry -> m MetadataEntry #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MetadataEntry -> m MetadataEntry #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MetadataEntry -> m MetadataEntry #

Read MetadataEntry Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Show MetadataEntry Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Generic MetadataEntry Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Associated Types

type Rep MetadataEntry :: Type -> Type #

Hashable MetadataEntry Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

ToXML MetadataEntry Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

toXML :: MetadataEntry -> XML #

NFData MetadataEntry Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

rnf :: MetadataEntry -> () #

type Rep MetadataEntry Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

type Rep MetadataEntry = D1 (MetaData "MetadataEntry" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" False) (C1 (MetaCons "MetadataEntry'" PrefixI True) (S1 (MetaSel (Just "_meValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_meName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))

metadataEntry :: MetadataEntry Source #

Creates a value of MetadataEntry with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

meValue :: Lens' MetadataEntry (Maybe Text) Source #

Undocumented member.

meName :: Lens' MetadataEntry (Maybe Text) Source #

Undocumented member.

MetricsAndOperator

data MetricsAndOperator Source #

See: metricsAndOperator smart constructor.

Instances
Eq MetricsAndOperator Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Data MetricsAndOperator Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MetricsAndOperator -> c MetricsAndOperator #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c MetricsAndOperator #

toConstr :: MetricsAndOperator -> Constr #

dataTypeOf :: MetricsAndOperator -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c MetricsAndOperator) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MetricsAndOperator) #

gmapT :: (forall b. Data b => b -> b) -> MetricsAndOperator -> MetricsAndOperator #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MetricsAndOperator -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MetricsAndOperator -> r #

gmapQ :: (forall d. Data d => d -> u) -> MetricsAndOperator -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MetricsAndOperator -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MetricsAndOperator -> m MetricsAndOperator #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MetricsAndOperator -> m MetricsAndOperator #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MetricsAndOperator -> m MetricsAndOperator #

Read MetricsAndOperator Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Show MetricsAndOperator Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Generic MetricsAndOperator Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Associated Types

type Rep MetricsAndOperator :: Type -> Type #

Hashable MetricsAndOperator Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

FromXML MetricsAndOperator Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

ToXML MetricsAndOperator Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

NFData MetricsAndOperator Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

rnf :: MetricsAndOperator -> () #

type Rep MetricsAndOperator Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

type Rep MetricsAndOperator = D1 (MetaData "MetricsAndOperator" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" False) (C1 (MetaCons "MetricsAndOperator'" PrefixI True) (S1 (MetaSel (Just "_maoPrefix") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_maoTags") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Tag]))))

metricsAndOperator :: MetricsAndOperator Source #

Creates a value of MetricsAndOperator with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • maoPrefix - The prefix used when evaluating an AND predicate.
  • maoTags - The list of tags used when evaluating an AND predicate.

maoPrefix :: Lens' MetricsAndOperator (Maybe Text) Source #

The prefix used when evaluating an AND predicate.

maoTags :: Lens' MetricsAndOperator [Tag] Source #

The list of tags used when evaluating an AND predicate.

MetricsConfiguration

data MetricsConfiguration Source #

See: metricsConfiguration smart constructor.

Instances
Eq MetricsConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Data MetricsConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MetricsConfiguration -> c MetricsConfiguration #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c MetricsConfiguration #

toConstr :: MetricsConfiguration -> Constr #

dataTypeOf :: MetricsConfiguration -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c MetricsConfiguration) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MetricsConfiguration) #

gmapT :: (forall b. Data b => b -> b) -> MetricsConfiguration -> MetricsConfiguration #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MetricsConfiguration -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MetricsConfiguration -> r #

gmapQ :: (forall d. Data d => d -> u) -> MetricsConfiguration -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MetricsConfiguration -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MetricsConfiguration -> m MetricsConfiguration #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MetricsConfiguration -> m MetricsConfiguration #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MetricsConfiguration -> m MetricsConfiguration #

Read MetricsConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Show MetricsConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Generic MetricsConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Associated Types

type Rep MetricsConfiguration :: Type -> Type #

Hashable MetricsConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

FromXML MetricsConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

ToXML MetricsConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

NFData MetricsConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

rnf :: MetricsConfiguration -> () #

type Rep MetricsConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

type Rep MetricsConfiguration = D1 (MetaData "MetricsConfiguration" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" False) (C1 (MetaCons "MetricsConfiguration'" PrefixI True) (S1 (MetaSel (Just "_mcFilter") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe MetricsFilter)) :*: S1 (MetaSel (Just "_mcId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)))

metricsConfiguration Source #

Creates a value of MetricsConfiguration with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • mcFilter - Specifies a metrics configuration filter. The metrics configuration will only include objects that meet the filter's criteria. A filter must be a prefix, a tag, or a conjunction (MetricsAndOperator).
  • mcId - The ID used to identify the metrics configuration.

mcFilter :: Lens' MetricsConfiguration (Maybe MetricsFilter) Source #

Specifies a metrics configuration filter. The metrics configuration will only include objects that meet the filter's criteria. A filter must be a prefix, a tag, or a conjunction (MetricsAndOperator).

mcId :: Lens' MetricsConfiguration Text Source #

The ID used to identify the metrics configuration.

MetricsFilter

data MetricsFilter Source #

See: metricsFilter smart constructor.

Instances
Eq MetricsFilter Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Data MetricsFilter Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MetricsFilter -> c MetricsFilter #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c MetricsFilter #

toConstr :: MetricsFilter -> Constr #

dataTypeOf :: MetricsFilter -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c MetricsFilter) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MetricsFilter) #

gmapT :: (forall b. Data b => b -> b) -> MetricsFilter -> MetricsFilter #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MetricsFilter -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MetricsFilter -> r #

gmapQ :: (forall d. Data d => d -> u) -> MetricsFilter -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MetricsFilter -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MetricsFilter -> m MetricsFilter #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MetricsFilter -> m MetricsFilter #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MetricsFilter -> m MetricsFilter #

Read MetricsFilter Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Show MetricsFilter Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Generic MetricsFilter Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Associated Types

type Rep MetricsFilter :: Type -> Type #

Hashable MetricsFilter Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

FromXML MetricsFilter Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

ToXML MetricsFilter Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

toXML :: MetricsFilter -> XML #

NFData MetricsFilter Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

rnf :: MetricsFilter -> () #

type Rep MetricsFilter Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

type Rep MetricsFilter = D1 (MetaData "MetricsFilter" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" False) (C1 (MetaCons "MetricsFilter'" PrefixI True) (S1 (MetaSel (Just "_mfTag") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Tag)) :*: (S1 (MetaSel (Just "_mfPrefix") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_mfAnd") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe MetricsAndOperator)))))

metricsFilter :: MetricsFilter Source #

Creates a value of MetricsFilter with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • mfTag - The tag used when evaluating a metrics filter.
  • mfPrefix - The prefix used when evaluating a metrics filter.
  • mfAnd - A conjunction (logical AND) of predicates, which is used in evaluating a metrics filter. The operator must have at least two predicates, and an object must match all of the predicates in order for the filter to apply.

mfTag :: Lens' MetricsFilter (Maybe Tag) Source #

The tag used when evaluating a metrics filter.

mfPrefix :: Lens' MetricsFilter (Maybe Text) Source #

The prefix used when evaluating a metrics filter.

mfAnd :: Lens' MetricsFilter (Maybe MetricsAndOperator) Source #

A conjunction (logical AND) of predicates, which is used in evaluating a metrics filter. The operator must have at least two predicates, and an object must match all of the predicates in order for the filter to apply.

MultipartUpload

data MultipartUpload Source #

See: multipartUpload smart constructor.

Instances
Eq MultipartUpload Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Data MultipartUpload Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MultipartUpload -> c MultipartUpload #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c MultipartUpload #

toConstr :: MultipartUpload -> Constr #

dataTypeOf :: MultipartUpload -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c MultipartUpload) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MultipartUpload) #

gmapT :: (forall b. Data b => b -> b) -> MultipartUpload -> MultipartUpload #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MultipartUpload -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MultipartUpload -> r #

gmapQ :: (forall d. Data d => d -> u) -> MultipartUpload -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MultipartUpload -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MultipartUpload -> m MultipartUpload #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MultipartUpload -> m MultipartUpload #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MultipartUpload -> m MultipartUpload #

Read MultipartUpload Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Show MultipartUpload Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Generic MultipartUpload Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Associated Types

type Rep MultipartUpload :: Type -> Type #

Hashable MultipartUpload Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

FromXML MultipartUpload Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

NFData MultipartUpload Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

rnf :: MultipartUpload -> () #

type Rep MultipartUpload Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

multipartUpload :: MultipartUpload Source #

Creates a value of MultipartUpload with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • muInitiated - Date and time at which the multipart upload was initiated.
  • muInitiator - Identifies who initiated the multipart upload.
  • muOwner - Undocumented member.
  • muKey - Key of the object for which the multipart upload was initiated.
  • muStorageClass - The class of storage used to store the object.
  • muUploadId - Upload ID that identifies the multipart upload.

muInitiated :: Lens' MultipartUpload (Maybe UTCTime) Source #

Date and time at which the multipart upload was initiated.

muInitiator :: Lens' MultipartUpload (Maybe Initiator) Source #

Identifies who initiated the multipart upload.

muOwner :: Lens' MultipartUpload (Maybe Owner) Source #

Undocumented member.

muKey :: Lens' MultipartUpload (Maybe ObjectKey) Source #

Key of the object for which the multipart upload was initiated.

muStorageClass :: Lens' MultipartUpload (Maybe StorageClass) Source #

The class of storage used to store the object.

muUploadId :: Lens' MultipartUpload (Maybe Text) Source #

Upload ID that identifies the multipart upload.

NoncurrentVersionExpiration

data NoncurrentVersionExpiration Source #

Specifies when noncurrent object versions expire. Upon expiration, Amazon S3 permanently deletes the noncurrent object versions. You set this lifecycle configuration action on a bucket that has versioning enabled (or suspended) to request that Amazon S3 delete noncurrent object versions at a specific period in the object's lifetime.

See: noncurrentVersionExpiration smart constructor.

Instances
Eq NoncurrentVersionExpiration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Data NoncurrentVersionExpiration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> NoncurrentVersionExpiration -> c NoncurrentVersionExpiration #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c NoncurrentVersionExpiration #

toConstr :: NoncurrentVersionExpiration -> Constr #

dataTypeOf :: NoncurrentVersionExpiration -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c NoncurrentVersionExpiration) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c NoncurrentVersionExpiration) #

gmapT :: (forall b. Data b => b -> b) -> NoncurrentVersionExpiration -> NoncurrentVersionExpiration #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NoncurrentVersionExpiration -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NoncurrentVersionExpiration -> r #

gmapQ :: (forall d. Data d => d -> u) -> NoncurrentVersionExpiration -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> NoncurrentVersionExpiration -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> NoncurrentVersionExpiration -> m NoncurrentVersionExpiration #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> NoncurrentVersionExpiration -> m NoncurrentVersionExpiration #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> NoncurrentVersionExpiration -> m NoncurrentVersionExpiration #

Read NoncurrentVersionExpiration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Show NoncurrentVersionExpiration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Generic NoncurrentVersionExpiration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Associated Types

type Rep NoncurrentVersionExpiration :: Type -> Type #

Hashable NoncurrentVersionExpiration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

FromXML NoncurrentVersionExpiration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

ToXML NoncurrentVersionExpiration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

NFData NoncurrentVersionExpiration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

type Rep NoncurrentVersionExpiration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

type Rep NoncurrentVersionExpiration = D1 (MetaData "NoncurrentVersionExpiration" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" True) (C1 (MetaCons "NoncurrentVersionExpiration'" PrefixI True) (S1 (MetaSel (Just "_nveNoncurrentDays") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)))

noncurrentVersionExpiration Source #

Creates a value of NoncurrentVersionExpiration with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

NoncurrentVersionTransition

data NoncurrentVersionTransition Source #

Container for the transition rule that describes when noncurrent objects transition to the STANDARD_IA, ONEZONE_IA or GLACIER storage class. If your bucket is versioning-enabled (or versioning is suspended), you can set this action to request that Amazon S3 transition noncurrent object versions to the STANDARD_IA, ONEZONE_IA or GLACIER storage class at a specific period in the object's lifetime.

See: noncurrentVersionTransition smart constructor.

Instances
Eq NoncurrentVersionTransition Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Data NoncurrentVersionTransition Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> NoncurrentVersionTransition -> c NoncurrentVersionTransition #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c NoncurrentVersionTransition #

toConstr :: NoncurrentVersionTransition -> Constr #

dataTypeOf :: NoncurrentVersionTransition -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c NoncurrentVersionTransition) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c NoncurrentVersionTransition) #

gmapT :: (forall b. Data b => b -> b) -> NoncurrentVersionTransition -> NoncurrentVersionTransition #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NoncurrentVersionTransition -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NoncurrentVersionTransition -> r #

gmapQ :: (forall d. Data d => d -> u) -> NoncurrentVersionTransition -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> NoncurrentVersionTransition -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> NoncurrentVersionTransition -> m NoncurrentVersionTransition #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> NoncurrentVersionTransition -> m NoncurrentVersionTransition #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> NoncurrentVersionTransition -> m NoncurrentVersionTransition #

Read NoncurrentVersionTransition Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Show NoncurrentVersionTransition Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Generic NoncurrentVersionTransition Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Associated Types

type Rep NoncurrentVersionTransition :: Type -> Type #

Hashable NoncurrentVersionTransition Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

FromXML NoncurrentVersionTransition Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

ToXML NoncurrentVersionTransition Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

NFData NoncurrentVersionTransition Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

type Rep NoncurrentVersionTransition Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

type Rep NoncurrentVersionTransition = D1 (MetaData "NoncurrentVersionTransition" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" False) (C1 (MetaCons "NoncurrentVersionTransition'" PrefixI True) (S1 (MetaSel (Just "_nvtNoncurrentDays") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int) :*: S1 (MetaSel (Just "_nvtStorageClass") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 TransitionStorageClass)))

noncurrentVersionTransition Source #

Creates a value of NoncurrentVersionTransition with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

nvtStorageClass :: Lens' NoncurrentVersionTransition TransitionStorageClass Source #

The class of storage used to store the object.

NotificationConfiguration

data NotificationConfiguration Source #

Container for specifying the notification configuration of the bucket. If this element is empty, notifications are turned off on the bucket.

See: notificationConfiguration smart constructor.

Instances
Eq NotificationConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Data NotificationConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> NotificationConfiguration -> c NotificationConfiguration #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c NotificationConfiguration #

toConstr :: NotificationConfiguration -> Constr #

dataTypeOf :: NotificationConfiguration -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c NotificationConfiguration) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c NotificationConfiguration) #

gmapT :: (forall b. Data b => b -> b) -> NotificationConfiguration -> NotificationConfiguration #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NotificationConfiguration -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NotificationConfiguration -> r #

gmapQ :: (forall d. Data d => d -> u) -> NotificationConfiguration -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> NotificationConfiguration -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> NotificationConfiguration -> m NotificationConfiguration #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> NotificationConfiguration -> m NotificationConfiguration #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> NotificationConfiguration -> m NotificationConfiguration #

Read NotificationConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Show NotificationConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Generic NotificationConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Associated Types

type Rep NotificationConfiguration :: Type -> Type #

Hashable NotificationConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

FromXML NotificationConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

ToXML NotificationConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

NFData NotificationConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

type Rep NotificationConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

type Rep NotificationConfiguration = D1 (MetaData "NotificationConfiguration" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" False) (C1 (MetaCons "NotificationConfiguration'" PrefixI True) (S1 (MetaSel (Just "_ncQueueConfigurations") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [QueueConfiguration])) :*: (S1 (MetaSel (Just "_ncTopicConfigurations") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [TopicConfiguration])) :*: S1 (MetaSel (Just "_ncLambdaFunctionConfigurations") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [LambdaFunctionConfiguration])))))

notificationConfiguration :: NotificationConfiguration Source #

Creates a value of NotificationConfiguration with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

NotificationConfigurationFilter

data NotificationConfigurationFilter Source #

Instances
Eq NotificationConfigurationFilter Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Data NotificationConfigurationFilter Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> NotificationConfigurationFilter -> c NotificationConfigurationFilter #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c NotificationConfigurationFilter #

toConstr :: NotificationConfigurationFilter -> Constr #

dataTypeOf :: NotificationConfigurationFilter -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c NotificationConfigurationFilter) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c NotificationConfigurationFilter) #

gmapT :: (forall b. Data b => b -> b) -> NotificationConfigurationFilter -> NotificationConfigurationFilter #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NotificationConfigurationFilter -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NotificationConfigurationFilter -> r #

gmapQ :: (forall d. Data d => d -> u) -> NotificationConfigurationFilter -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> NotificationConfigurationFilter -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> NotificationConfigurationFilter -> m NotificationConfigurationFilter #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> NotificationConfigurationFilter -> m NotificationConfigurationFilter #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> NotificationConfigurationFilter -> m NotificationConfigurationFilter #

Read NotificationConfigurationFilter Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Show NotificationConfigurationFilter Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Generic NotificationConfigurationFilter Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Associated Types

type Rep NotificationConfigurationFilter :: Type -> Type #

Hashable NotificationConfigurationFilter Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

FromXML NotificationConfigurationFilter Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

ToXML NotificationConfigurationFilter Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

NFData NotificationConfigurationFilter Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

type Rep NotificationConfigurationFilter Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

type Rep NotificationConfigurationFilter = D1 (MetaData "NotificationConfigurationFilter" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" True) (C1 (MetaCons "NotificationConfigurationFilter'" PrefixI True) (S1 (MetaSel (Just "_ncfKey") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe S3KeyFilter))))

notificationConfigurationFilter :: NotificationConfigurationFilter Source #

Creates a value of NotificationConfigurationFilter with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

Object

data Object Source #

See: object' smart constructor.

Instances
Eq Object Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

(==) :: Object -> Object -> Bool #

(/=) :: Object -> Object -> Bool #

Data Object Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

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 #

Read Object Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Show Object Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Generic Object Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Associated Types

type Rep Object :: Type -> Type #

Methods

from :: Object -> Rep Object x #

to :: Rep Object x -> Object #

Hashable Object Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

hashWithSalt :: Int -> Object -> Int #

hash :: Object -> Int #

FromXML Object Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

NFData Object Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

rnf :: Object -> () #

type Rep Object Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

object' Source #

Creates a value of Object with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

oOwner :: Lens' Object (Maybe Owner) Source #

Undocumented member.

oETag :: Lens' Object ETag Source #

Undocumented member.

oSize :: Lens' Object Int Source #

Undocumented member.

oKey :: Lens' Object ObjectKey Source #

Undocumented member.

oStorageClass :: Lens' Object ObjectStorageClass Source #

The class of storage used to store the object.

oLastModified :: Lens' Object UTCTime Source #

Undocumented member.

ObjectIdentifier

data ObjectIdentifier Source #

See: objectIdentifier smart constructor.

Instances
Eq ObjectIdentifier Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Data ObjectIdentifier Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ObjectIdentifier -> c ObjectIdentifier #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ObjectIdentifier #

toConstr :: ObjectIdentifier -> Constr #

dataTypeOf :: ObjectIdentifier -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ObjectIdentifier) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ObjectIdentifier) #

gmapT :: (forall b. Data b => b -> b) -> ObjectIdentifier -> ObjectIdentifier #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ObjectIdentifier -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ObjectIdentifier -> r #

gmapQ :: (forall d. Data d => d -> u) -> ObjectIdentifier -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ObjectIdentifier -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ObjectIdentifier -> m ObjectIdentifier #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ObjectIdentifier -> m ObjectIdentifier #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ObjectIdentifier -> m ObjectIdentifier #

Read ObjectIdentifier Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Show ObjectIdentifier Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Generic ObjectIdentifier Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Associated Types

type Rep ObjectIdentifier :: Type -> Type #

Hashable ObjectIdentifier Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

ToXML ObjectIdentifier Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

NFData ObjectIdentifier Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

rnf :: ObjectIdentifier -> () #

type Rep ObjectIdentifier Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

type Rep ObjectIdentifier = D1 (MetaData "ObjectIdentifier" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" False) (C1 (MetaCons "ObjectIdentifier'" PrefixI True) (S1 (MetaSel (Just "_oiVersionId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ObjectVersionId)) :*: S1 (MetaSel (Just "_oiKey") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 ObjectKey)))

objectIdentifier Source #

Creates a value of ObjectIdentifier with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • oiVersionId - VersionId for the specific version of the object to delete.
  • oiKey - Key name of the object to delete.

oiVersionId :: Lens' ObjectIdentifier (Maybe ObjectVersionId) Source #

VersionId for the specific version of the object to delete.

oiKey :: Lens' ObjectIdentifier ObjectKey Source #

Key name of the object to delete.

ObjectVersion

data ObjectVersion Source #

See: objectVersion smart constructor.

Instances
Eq ObjectVersion Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Data ObjectVersion Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ObjectVersion -> c ObjectVersion #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ObjectVersion #

toConstr :: ObjectVersion -> Constr #

dataTypeOf :: ObjectVersion -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ObjectVersion) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ObjectVersion) #

gmapT :: (forall b. Data b => b -> b) -> ObjectVersion -> ObjectVersion #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ObjectVersion -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ObjectVersion -> r #

gmapQ :: (forall d. Data d => d -> u) -> ObjectVersion -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ObjectVersion -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ObjectVersion -> m ObjectVersion #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ObjectVersion -> m ObjectVersion #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ObjectVersion -> m ObjectVersion #

Read ObjectVersion Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Show ObjectVersion Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Generic ObjectVersion Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Associated Types

type Rep ObjectVersion :: Type -> Type #

Hashable ObjectVersion Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

FromXML ObjectVersion Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

NFData ObjectVersion Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

rnf :: ObjectVersion -> () #

type Rep ObjectVersion Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

objectVersion :: ObjectVersion Source #

Creates a value of ObjectVersion with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • ovETag - Undocumented member.
  • ovVersionId - Version ID of an object.
  • ovSize - Size in bytes of the object.
  • ovIsLatest - Specifies whether the object is (true) or is not (false) the latest version of an object.
  • ovOwner - Undocumented member.
  • ovKey - The object key.
  • ovStorageClass - The class of storage used to store the object.
  • ovLastModified - Date and time the object was last modified.

ovETag :: Lens' ObjectVersion (Maybe ETag) Source #

Undocumented member.

ovSize :: Lens' ObjectVersion (Maybe Int) Source #

Size in bytes of the object.

ovIsLatest :: Lens' ObjectVersion (Maybe Bool) Source #

Specifies whether the object is (true) or is not (false) the latest version of an object.

ovOwner :: Lens' ObjectVersion (Maybe Owner) Source #

Undocumented member.

ovStorageClass :: Lens' ObjectVersion (Maybe ObjectVersionStorageClass) Source #

The class of storage used to store the object.

ovLastModified :: Lens' ObjectVersion (Maybe UTCTime) Source #

Date and time the object was last modified.

OutputLocation

data OutputLocation Source #

Describes the location where the restore job's output is stored.

See: outputLocation smart constructor.

Instances
Eq OutputLocation Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Data OutputLocation Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> OutputLocation -> c OutputLocation #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c OutputLocation #

toConstr :: OutputLocation -> Constr #

dataTypeOf :: OutputLocation -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c OutputLocation) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c OutputLocation) #

gmapT :: (forall b. Data b => b -> b) -> OutputLocation -> OutputLocation #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> OutputLocation -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> OutputLocation -> r #

gmapQ :: (forall d. Data d => d -> u) -> OutputLocation -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> OutputLocation -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> OutputLocation -> m OutputLocation #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> OutputLocation -> m OutputLocation #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> OutputLocation -> m OutputLocation #

Show OutputLocation Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Generic OutputLocation Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Associated Types

type Rep OutputLocation :: Type -> Type #

Hashable OutputLocation Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

ToXML OutputLocation Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

toXML :: OutputLocation -> XML #

NFData OutputLocation Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

rnf :: OutputLocation -> () #

type Rep OutputLocation Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

type Rep OutputLocation = D1 (MetaData "OutputLocation" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" True) (C1 (MetaCons "OutputLocation'" PrefixI True) (S1 (MetaSel (Just "_olS3") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe S3Location))))

outputLocation :: OutputLocation Source #

Creates a value of OutputLocation with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • olS3 - Describes an S3 location that will receive the results of the restore request.

olS3 :: Lens' OutputLocation (Maybe S3Location) Source #

Describes an S3 location that will receive the results of the restore request.

OutputSerialization

data OutputSerialization Source #

Describes how results of the Select job are serialized.

See: outputSerialization smart constructor.

Instances
Eq OutputSerialization Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Data OutputSerialization Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> OutputSerialization -> c OutputSerialization #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c OutputSerialization #

toConstr :: OutputSerialization -> Constr #

dataTypeOf :: OutputSerialization -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c OutputSerialization) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c OutputSerialization) #

gmapT :: (forall b. Data b => b -> b) -> OutputSerialization -> OutputSerialization #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> OutputSerialization -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> OutputSerialization -> r #

gmapQ :: (forall d. Data d => d -> u) -> OutputSerialization -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> OutputSerialization -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> OutputSerialization -> m OutputSerialization #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> OutputSerialization -> m OutputSerialization #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> OutputSerialization -> m OutputSerialization #

Read OutputSerialization Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Show OutputSerialization Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Generic OutputSerialization Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Associated Types

type Rep OutputSerialization :: Type -> Type #

Hashable OutputSerialization Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

ToXML OutputSerialization Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

NFData OutputSerialization Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

rnf :: OutputSerialization -> () #

type Rep OutputSerialization Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

type Rep OutputSerialization = D1 (MetaData "OutputSerialization" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" False) (C1 (MetaCons "OutputSerialization'" PrefixI True) (S1 (MetaSel (Just "_osJSON") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe JSONOutput)) :*: S1 (MetaSel (Just "_osCSV") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe CSVOutput))))

outputSerialization :: OutputSerialization Source #

Creates a value of OutputSerialization with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • osJSON - Specifies JSON as request's output serialization format.
  • osCSV - Describes the serialization of CSV-encoded Select results.

osJSON :: Lens' OutputSerialization (Maybe JSONOutput) Source #

Specifies JSON as request's output serialization format.

osCSV :: Lens' OutputSerialization (Maybe CSVOutput) Source #

Describes the serialization of CSV-encoded Select results.

Owner

data Owner Source #

See: owner smart constructor.

Instances
Eq Owner Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

(==) :: Owner -> Owner -> Bool #

(/=) :: Owner -> Owner -> Bool #

Data Owner Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Owner -> c Owner #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Owner #

toConstr :: Owner -> Constr #

dataTypeOf :: Owner -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Owner) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Owner) #

gmapT :: (forall b. Data b => b -> b) -> Owner -> Owner #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Owner -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Owner -> r #

gmapQ :: (forall d. Data d => d -> u) -> Owner -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Owner -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Owner -> m Owner #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Owner -> m Owner #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Owner -> m Owner #

Read Owner Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Show Owner Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

showsPrec :: Int -> Owner -> ShowS #

show :: Owner -> String #

showList :: [Owner] -> ShowS #

Generic Owner Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Associated Types

type Rep Owner :: Type -> Type #

Methods

from :: Owner -> Rep Owner x #

to :: Rep Owner x -> Owner #

Hashable Owner Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

hashWithSalt :: Int -> Owner -> Int #

hash :: Owner -> Int #

FromXML Owner Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

parseXML :: [Node] -> Either String Owner #

ToXML Owner Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

toXML :: Owner -> XML #

NFData Owner Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

rnf :: Owner -> () #

type Rep Owner Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

type Rep Owner = D1 (MetaData "Owner" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" False) (C1 (MetaCons "Owner'" PrefixI True) (S1 (MetaSel (Just "_oDisplayName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_oId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))

owner :: Owner Source #

Creates a value of Owner with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

oDisplayName :: Lens' Owner (Maybe Text) Source #

Undocumented member.

oId :: Lens' Owner (Maybe Text) Source #

Undocumented member.

Part

data Part Source #

See: part smart constructor.

Instances
Eq Part Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

(==) :: Part -> Part -> Bool #

(/=) :: Part -> Part -> Bool #

Data Part Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Part -> c Part #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Part #

toConstr :: Part -> Constr #

dataTypeOf :: Part -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Part) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Part) #

gmapT :: (forall b. Data b => b -> b) -> Part -> Part #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Part -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Part -> r #

gmapQ :: (forall d. Data d => d -> u) -> Part -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Part -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Part -> m Part #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Part -> m Part #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Part -> m Part #

Read Part Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Show Part Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

showsPrec :: Int -> Part -> ShowS #

show :: Part -> String #

showList :: [Part] -> ShowS #

Generic Part Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Associated Types

type Rep Part :: Type -> Type #

Methods

from :: Part -> Rep Part x #

to :: Rep Part x -> Part #

Hashable Part Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

hashWithSalt :: Int -> Part -> Int #

hash :: Part -> Int #

FromXML Part Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

parseXML :: [Node] -> Either String Part #

NFData Part Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

rnf :: Part -> () #

type Rep Part Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

type Rep Part = D1 (MetaData "Part" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" False) (C1 (MetaCons "Part'" PrefixI True) ((S1 (MetaSel (Just "_pETag") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ETag)) :*: S1 (MetaSel (Just "_pSize") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Int))) :*: (S1 (MetaSel (Just "_pPartNumber") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Int)) :*: S1 (MetaSel (Just "_pLastModified") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe RFC822)))))

part :: Part Source #

Creates a value of Part with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • pETag - Entity tag returned when the part was uploaded.
  • pSize - Size of the uploaded part data.
  • pPartNumber - Part number identifying the part. This is a positive integer between 1 and 10,000.
  • pLastModified - Date and time at which the part was uploaded.

pETag :: Lens' Part (Maybe ETag) Source #

Entity tag returned when the part was uploaded.

pSize :: Lens' Part (Maybe Int) Source #

Size of the uploaded part data.

pPartNumber :: Lens' Part (Maybe Int) Source #

Part number identifying the part. This is a positive integer between 1 and 10,000.

pLastModified :: Lens' Part (Maybe UTCTime) Source #

Date and time at which the part was uploaded.

Progress

data Progress Source #

See: progress smart constructor.

Instances
Eq Progress Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Data Progress Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Progress -> c Progress #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Progress #

toConstr :: Progress -> Constr #

dataTypeOf :: Progress -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Progress) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Progress) #

gmapT :: (forall b. Data b => b -> b) -> Progress -> Progress #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Progress -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Progress -> r #

gmapQ :: (forall d. Data d => d -> u) -> Progress -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Progress -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Progress -> m Progress #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Progress -> m Progress #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Progress -> m Progress #

Read Progress Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Show Progress Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Generic Progress Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Associated Types

type Rep Progress :: Type -> Type #

Methods

from :: Progress -> Rep Progress x #

to :: Rep Progress x -> Progress #

Hashable Progress Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

hashWithSalt :: Int -> Progress -> Int #

hash :: Progress -> Int #

FromXML Progress Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

NFData Progress Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

rnf :: Progress -> () #

type Rep Progress Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

type Rep Progress = D1 (MetaData "Progress" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" False) (C1 (MetaCons "Progress'" PrefixI True) (S1 (MetaSel (Just "_pBytesReturned") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Integer)) :*: (S1 (MetaSel (Just "_pBytesScanned") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Integer)) :*: S1 (MetaSel (Just "_pBytesProcessed") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Integer)))))

progress :: Progress Source #

Creates a value of Progress with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

pBytesReturned :: Lens' Progress (Maybe Integer) Source #

Current number of bytes of records payload data returned.

pBytesScanned :: Lens' Progress (Maybe Integer) Source #

Current number of object bytes scanned.

pBytesProcessed :: Lens' Progress (Maybe Integer) Source #

Current number of uncompressed object bytes processed.

ProgressEvent

data ProgressEvent Source #

See: progressEvent smart constructor.

Instances
Eq ProgressEvent Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Data ProgressEvent Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ProgressEvent -> c ProgressEvent #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ProgressEvent #

toConstr :: ProgressEvent -> Constr #

dataTypeOf :: ProgressEvent -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ProgressEvent) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ProgressEvent) #

gmapT :: (forall b. Data b => b -> b) -> ProgressEvent -> ProgressEvent #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ProgressEvent -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ProgressEvent -> r #

gmapQ :: (forall d. Data d => d -> u) -> ProgressEvent -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ProgressEvent -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ProgressEvent -> m ProgressEvent #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ProgressEvent -> m ProgressEvent #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ProgressEvent -> m ProgressEvent #

Read ProgressEvent Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Show ProgressEvent Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Generic ProgressEvent Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Associated Types

type Rep ProgressEvent :: Type -> Type #

Hashable ProgressEvent Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

FromXML ProgressEvent Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

NFData ProgressEvent Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

rnf :: ProgressEvent -> () #

type Rep ProgressEvent Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

type Rep ProgressEvent = D1 (MetaData "ProgressEvent" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" True) (C1 (MetaCons "ProgressEvent'" PrefixI True) (S1 (MetaSel (Just "_peDetails") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Progress))))

progressEvent :: ProgressEvent Source #

Creates a value of ProgressEvent with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

peDetails :: Lens' ProgressEvent (Maybe Progress) Source #

The Progress event details.

QueueConfiguration

data QueueConfiguration Source #

Container for specifying an configuration when you want Amazon S3 to publish events to an Amazon Simple Queue Service (Amazon SQS) queue.

See: queueConfiguration smart constructor.

Instances
Eq QueueConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Data QueueConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> QueueConfiguration -> c QueueConfiguration #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c QueueConfiguration #

toConstr :: QueueConfiguration -> Constr #

dataTypeOf :: QueueConfiguration -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c QueueConfiguration) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c QueueConfiguration) #

gmapT :: (forall b. Data b => b -> b) -> QueueConfiguration -> QueueConfiguration #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> QueueConfiguration -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> QueueConfiguration -> r #

gmapQ :: (forall d. Data d => d -> u) -> QueueConfiguration -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> QueueConfiguration -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> QueueConfiguration -> m QueueConfiguration #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> QueueConfiguration -> m QueueConfiguration #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> QueueConfiguration -> m QueueConfiguration #

Read QueueConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Show QueueConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Generic QueueConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Associated Types

type Rep QueueConfiguration :: Type -> Type #

Hashable QueueConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

FromXML QueueConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

ToXML QueueConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

NFData QueueConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

rnf :: QueueConfiguration -> () #

type Rep QueueConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

type Rep QueueConfiguration = D1 (MetaData "QueueConfiguration" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" False) (C1 (MetaCons "QueueConfiguration'" PrefixI True) ((S1 (MetaSel (Just "_qcId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_qcFilter") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe NotificationConfigurationFilter))) :*: (S1 (MetaSel (Just "_qcQueueARN") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text) :*: S1 (MetaSel (Just "_qcEvents") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [Event]))))

queueConfiguration Source #

Creates a value of QueueConfiguration with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • qcId - Undocumented member.
  • qcFilter - Undocumented member.
  • qcQueueARN - Amazon SQS queue ARN to which Amazon S3 will publish a message when it detects events of specified type.
  • qcEvents - Undocumented member.

qcId :: Lens' QueueConfiguration (Maybe Text) Source #

Undocumented member.

qcQueueARN :: Lens' QueueConfiguration Text Source #

Amazon SQS queue ARN to which Amazon S3 will publish a message when it detects events of specified type.

qcEvents :: Lens' QueueConfiguration [Event] Source #

Undocumented member.

RecordsEvent

data RecordsEvent Source #

See: recordsEvent smart constructor.

Instances
Eq RecordsEvent Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Data RecordsEvent Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RecordsEvent -> c RecordsEvent #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RecordsEvent #

toConstr :: RecordsEvent -> Constr #

dataTypeOf :: RecordsEvent -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c RecordsEvent) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RecordsEvent) #

gmapT :: (forall b. Data b => b -> b) -> RecordsEvent -> RecordsEvent #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RecordsEvent -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RecordsEvent -> r #

gmapQ :: (forall d. Data d => d -> u) -> RecordsEvent -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RecordsEvent -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RecordsEvent -> m RecordsEvent #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RecordsEvent -> m RecordsEvent #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RecordsEvent -> m RecordsEvent #

Read RecordsEvent Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Show RecordsEvent Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Generic RecordsEvent Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Associated Types

type Rep RecordsEvent :: Type -> Type #

Hashable RecordsEvent Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

FromXML RecordsEvent Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

NFData RecordsEvent Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

rnf :: RecordsEvent -> () #

type Rep RecordsEvent Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

type Rep RecordsEvent = D1 (MetaData "RecordsEvent" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" True) (C1 (MetaCons "RecordsEvent'" PrefixI True) (S1 (MetaSel (Just "_rePayload") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Base64))))

recordsEvent :: RecordsEvent Source #

Creates a value of RecordsEvent with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • rePayload - The byte array of partial, one or more result records.-- Note: This Lens automatically encodes and decodes Base64 data. The underlying isomorphism will encode to Base64 representation during serialisation, and decode from Base64 representation during deserialisation. This Lens accepts and returns only raw unencoded data.

rePayload :: Lens' RecordsEvent (Maybe ByteString) Source #

The byte array of partial, one or more result records.-- Note: This Lens automatically encodes and decodes Base64 data. The underlying isomorphism will encode to Base64 representation during serialisation, and decode from Base64 representation during deserialisation. This Lens accepts and returns only raw unencoded data.

Redirect

data Redirect Source #

See: redirect smart constructor.

Instances
Eq Redirect Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Data Redirect Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Redirect -> c Redirect #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Redirect #

toConstr :: Redirect -> Constr #

dataTypeOf :: Redirect -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Redirect) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Redirect) #

gmapT :: (forall b. Data b => b -> b) -> Redirect -> Redirect #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Redirect -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Redirect -> r #

gmapQ :: (forall d. Data d => d -> u) -> Redirect -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Redirect -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Redirect -> m Redirect #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Redirect -> m Redirect #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Redirect -> m Redirect #

Read Redirect Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Show Redirect Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Generic Redirect Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Associated Types

type Rep Redirect :: Type -> Type #

Methods

from :: Redirect -> Rep Redirect x #

to :: Rep Redirect x -> Redirect #

Hashable Redirect Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

hashWithSalt :: Int -> Redirect -> Int #

hash :: Redirect -> Int #

FromXML Redirect Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

ToXML Redirect Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

toXML :: Redirect -> XML #

NFData Redirect Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

rnf :: Redirect -> () #

type Rep Redirect Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

type Rep Redirect = D1 (MetaData "Redirect" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" False) (C1 (MetaCons "Redirect'" PrefixI True) ((S1 (MetaSel (Just "_rHostName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_rProtocol") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Protocol))) :*: (S1 (MetaSel (Just "_rHTTPRedirectCode") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: (S1 (MetaSel (Just "_rReplaceKeyWith") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_rReplaceKeyPrefixWith") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))))

redirect :: Redirect Source #

Creates a value of Redirect with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • rHostName - The host name to use in the redirect request.
  • rProtocol - Protocol to use (http, https) when redirecting requests. The default is the protocol that is used in the original request.
  • rHTTPRedirectCode - The HTTP redirect code to use on the response. Not required if one of the siblings is present.
  • rReplaceKeyWith - The specific object key to use in the redirect request. For example, redirect request to error.html. Not required if one of the sibling is present. Can be present only if ReplaceKeyPrefixWith is not provided.
  • rReplaceKeyPrefixWith - The object key prefix to use in the redirect request. For example, to redirect requests for all pages with prefix docs (objects in the docs folder) to documents, you can set a condition block with KeyPrefixEquals set to docs and in the Redirect set ReplaceKeyPrefixWith to /documents. Not required if one of the siblings is present. Can be present only if ReplaceKeyWith is not provided.

rHostName :: Lens' Redirect (Maybe Text) Source #

The host name to use in the redirect request.

rProtocol :: Lens' Redirect (Maybe Protocol) Source #

Protocol to use (http, https) when redirecting requests. The default is the protocol that is used in the original request.

rHTTPRedirectCode :: Lens' Redirect (Maybe Text) Source #

The HTTP redirect code to use on the response. Not required if one of the siblings is present.

rReplaceKeyWith :: Lens' Redirect (Maybe Text) Source #

The specific object key to use in the redirect request. For example, redirect request to error.html. Not required if one of the sibling is present. Can be present only if ReplaceKeyPrefixWith is not provided.

rReplaceKeyPrefixWith :: Lens' Redirect (Maybe Text) Source #

The object key prefix to use in the redirect request. For example, to redirect requests for all pages with prefix docs (objects in the docs folder) to documents, you can set a condition block with KeyPrefixEquals set to docs and in the Redirect set ReplaceKeyPrefixWith to /documents. Not required if one of the siblings is present. Can be present only if ReplaceKeyWith is not provided.

RedirectAllRequestsTo

data RedirectAllRequestsTo Source #

See: redirectAllRequestsTo smart constructor.

Instances
Eq RedirectAllRequestsTo Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Data RedirectAllRequestsTo Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RedirectAllRequestsTo -> c RedirectAllRequestsTo #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RedirectAllRequestsTo #

toConstr :: RedirectAllRequestsTo -> Constr #

dataTypeOf :: RedirectAllRequestsTo -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c RedirectAllRequestsTo) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RedirectAllRequestsTo) #

gmapT :: (forall b. Data b => b -> b) -> RedirectAllRequestsTo -> RedirectAllRequestsTo #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RedirectAllRequestsTo -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RedirectAllRequestsTo -> r #

gmapQ :: (forall d. Data d => d -> u) -> RedirectAllRequestsTo -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RedirectAllRequestsTo -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RedirectAllRequestsTo -> m RedirectAllRequestsTo #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RedirectAllRequestsTo -> m RedirectAllRequestsTo #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RedirectAllRequestsTo -> m RedirectAllRequestsTo #

Read RedirectAllRequestsTo Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Show RedirectAllRequestsTo Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Generic RedirectAllRequestsTo Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Associated Types

type Rep RedirectAllRequestsTo :: Type -> Type #

Hashable RedirectAllRequestsTo Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

FromXML RedirectAllRequestsTo Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

ToXML RedirectAllRequestsTo Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

NFData RedirectAllRequestsTo Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

rnf :: RedirectAllRequestsTo -> () #

type Rep RedirectAllRequestsTo Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

type Rep RedirectAllRequestsTo = D1 (MetaData "RedirectAllRequestsTo" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" False) (C1 (MetaCons "RedirectAllRequestsTo'" PrefixI True) (S1 (MetaSel (Just "_rartProtocol") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Protocol)) :*: S1 (MetaSel (Just "_rartHostName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)))

redirectAllRequestsTo Source #

Creates a value of RedirectAllRequestsTo with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • rartProtocol - Protocol to use (http, https) when redirecting requests. The default is the protocol that is used in the original request.
  • rartHostName - Name of the host where requests will be redirected.

rartProtocol :: Lens' RedirectAllRequestsTo (Maybe Protocol) Source #

Protocol to use (http, https) when redirecting requests. The default is the protocol that is used in the original request.

rartHostName :: Lens' RedirectAllRequestsTo Text Source #

Name of the host where requests will be redirected.

ReplicationConfiguration

data ReplicationConfiguration Source #

Container for replication rules. You can add as many as 1,000 rules. Total replication configuration size can be up to 2 MB.

See: replicationConfiguration smart constructor.

Instances
Eq ReplicationConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Data ReplicationConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ReplicationConfiguration -> c ReplicationConfiguration #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ReplicationConfiguration #

toConstr :: ReplicationConfiguration -> Constr #

dataTypeOf :: ReplicationConfiguration -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ReplicationConfiguration) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ReplicationConfiguration) #

gmapT :: (forall b. Data b => b -> b) -> ReplicationConfiguration -> ReplicationConfiguration #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ReplicationConfiguration -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ReplicationConfiguration -> r #

gmapQ :: (forall d. Data d => d -> u) -> ReplicationConfiguration -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ReplicationConfiguration -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ReplicationConfiguration -> m ReplicationConfiguration #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ReplicationConfiguration -> m ReplicationConfiguration #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ReplicationConfiguration -> m ReplicationConfiguration #

Read ReplicationConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Show ReplicationConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Generic ReplicationConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Associated Types

type Rep ReplicationConfiguration :: Type -> Type #

Hashable ReplicationConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

FromXML ReplicationConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

ToXML ReplicationConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

NFData ReplicationConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

type Rep ReplicationConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

type Rep ReplicationConfiguration = D1 (MetaData "ReplicationConfiguration" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" False) (C1 (MetaCons "ReplicationConfiguration'" PrefixI True) (S1 (MetaSel (Just "_rcRole") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text) :*: S1 (MetaSel (Just "_rcRules") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [ReplicationRule])))

replicationConfiguration Source #

Creates a value of ReplicationConfiguration with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • rcRole - Amazon Resource Name (ARN) of an IAM role for Amazon S3 to assume when replicating the objects.
  • rcRules - Container for information about a particular replication rule. Replication configuration must have at least one rule and can contain up to 1,000 rules.

rcRole :: Lens' ReplicationConfiguration Text Source #

Amazon Resource Name (ARN) of an IAM role for Amazon S3 to assume when replicating the objects.

rcRules :: Lens' ReplicationConfiguration [ReplicationRule] Source #

Container for information about a particular replication rule. Replication configuration must have at least one rule and can contain up to 1,000 rules.

ReplicationRule

data ReplicationRule Source #

Container for information about a particular replication rule.

See: replicationRule smart constructor.

Instances
Eq ReplicationRule Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Data ReplicationRule Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ReplicationRule -> c ReplicationRule #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ReplicationRule #

toConstr :: ReplicationRule -> Constr #

dataTypeOf :: ReplicationRule -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ReplicationRule) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ReplicationRule) #

gmapT :: (forall b. Data b => b -> b) -> ReplicationRule -> ReplicationRule #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ReplicationRule -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ReplicationRule -> r #

gmapQ :: (forall d. Data d => d -> u) -> ReplicationRule -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ReplicationRule -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ReplicationRule -> m ReplicationRule #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ReplicationRule -> m ReplicationRule #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ReplicationRule -> m ReplicationRule #

Read ReplicationRule Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Show ReplicationRule Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Generic ReplicationRule Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Associated Types

type Rep ReplicationRule :: Type -> Type #

Hashable ReplicationRule Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

FromXML ReplicationRule Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

ToXML ReplicationRule Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

toXML :: ReplicationRule -> XML #

NFData ReplicationRule Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

rnf :: ReplicationRule -> () #

type Rep ReplicationRule Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

replicationRule Source #

Creates a value of ReplicationRule with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • rrId - Unique identifier for the rule. The value cannot be longer than 255 characters.
  • rrSourceSelectionCriteria - Container for filters that define which source objects should be replicated.
  • rrPrefix - Object keyname prefix identifying one or more objects to which the rule applies. Maximum prefix length can be up to 1,024 characters. Overlapping prefixes are not supported.
  • rrStatus - The rule is ignored if status is not Enabled.
  • rrDestination - Container for replication destination information.

rrId :: Lens' ReplicationRule (Maybe Text) Source #

Unique identifier for the rule. The value cannot be longer than 255 characters.

rrSourceSelectionCriteria :: Lens' ReplicationRule (Maybe SourceSelectionCriteria) Source #

Container for filters that define which source objects should be replicated.

rrPrefix :: Lens' ReplicationRule Text Source #

Object keyname prefix identifying one or more objects to which the rule applies. Maximum prefix length can be up to 1,024 characters. Overlapping prefixes are not supported.

rrStatus :: Lens' ReplicationRule ReplicationRuleStatus Source #

The rule is ignored if status is not Enabled.

rrDestination :: Lens' ReplicationRule Destination Source #

Container for replication destination information.

RequestPaymentConfiguration

data RequestPaymentConfiguration Source #

See: requestPaymentConfiguration smart constructor.

Instances
Eq RequestPaymentConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Data RequestPaymentConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RequestPaymentConfiguration -> c RequestPaymentConfiguration #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RequestPaymentConfiguration #

toConstr :: RequestPaymentConfiguration -> Constr #

dataTypeOf :: RequestPaymentConfiguration -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c RequestPaymentConfiguration) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RequestPaymentConfiguration) #

gmapT :: (forall b. Data b => b -> b) -> RequestPaymentConfiguration -> RequestPaymentConfiguration #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RequestPaymentConfiguration -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RequestPaymentConfiguration -> r #

gmapQ :: (forall d. Data d => d -> u) -> RequestPaymentConfiguration -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RequestPaymentConfiguration -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RequestPaymentConfiguration -> m RequestPaymentConfiguration #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RequestPaymentConfiguration -> m RequestPaymentConfiguration #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RequestPaymentConfiguration -> m RequestPaymentConfiguration #

Read RequestPaymentConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Show RequestPaymentConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Generic RequestPaymentConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Associated Types

type Rep RequestPaymentConfiguration :: Type -> Type #

Hashable RequestPaymentConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

ToXML RequestPaymentConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

NFData RequestPaymentConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

type Rep RequestPaymentConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

type Rep RequestPaymentConfiguration = D1 (MetaData "RequestPaymentConfiguration" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" True) (C1 (MetaCons "RequestPaymentConfiguration'" PrefixI True) (S1 (MetaSel (Just "_rpcPayer") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Payer)))

requestPaymentConfiguration Source #

Creates a value of RequestPaymentConfiguration with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • rpcPayer - Specifies who pays for the download and request fees.

rpcPayer :: Lens' RequestPaymentConfiguration Payer Source #

Specifies who pays for the download and request fees.

RequestProgress

data RequestProgress Source #

See: requestProgress smart constructor.

Instances
Eq RequestProgress Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Data RequestProgress Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RequestProgress -> c RequestProgress #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RequestProgress #

toConstr :: RequestProgress -> Constr #

dataTypeOf :: RequestProgress -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c RequestProgress) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RequestProgress) #

gmapT :: (forall b. Data b => b -> b) -> RequestProgress -> RequestProgress #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RequestProgress -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RequestProgress -> r #

gmapQ :: (forall d. Data d => d -> u) -> RequestProgress -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RequestProgress -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RequestProgress -> m RequestProgress #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RequestProgress -> m RequestProgress #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RequestProgress -> m RequestProgress #

Read RequestProgress Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Show RequestProgress Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Generic RequestProgress Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Associated Types

type Rep RequestProgress :: Type -> Type #

Hashable RequestProgress Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

ToXML RequestProgress Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

toXML :: RequestProgress -> XML #

NFData RequestProgress Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

rnf :: RequestProgress -> () #

type Rep RequestProgress Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

type Rep RequestProgress = D1 (MetaData "RequestProgress" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" True) (C1 (MetaCons "RequestProgress'" PrefixI True) (S1 (MetaSel (Just "_rpEnabled") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Bool))))

requestProgress :: RequestProgress Source #

Creates a value of RequestProgress with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • rpEnabled - Specifies whether periodic QueryProgress frames should be sent. Valid values: TRUE, FALSE. Default value: FALSE.

rpEnabled :: Lens' RequestProgress (Maybe Bool) Source #

Specifies whether periodic QueryProgress frames should be sent. Valid values: TRUE, FALSE. Default value: FALSE.

RestoreRequest

data RestoreRequest Source #

Container for restore job parameters.

See: restoreRequest smart constructor.

Instances
Eq RestoreRequest Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Data RestoreRequest Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RestoreRequest -> c RestoreRequest #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RestoreRequest #

toConstr :: RestoreRequest -> Constr #

dataTypeOf :: RestoreRequest -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c RestoreRequest) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RestoreRequest) #

gmapT :: (forall b. Data b => b -> b) -> RestoreRequest -> RestoreRequest #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RestoreRequest -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RestoreRequest -> r #

gmapQ :: (forall d. Data d => d -> u) -> RestoreRequest -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RestoreRequest -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RestoreRequest -> m RestoreRequest #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RestoreRequest -> m RestoreRequest #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RestoreRequest -> m RestoreRequest #

Show RestoreRequest Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Generic RestoreRequest Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Associated Types

type Rep RestoreRequest :: Type -> Type #

Hashable RestoreRequest Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

ToXML RestoreRequest Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

toXML :: RestoreRequest -> XML #

NFData RestoreRequest Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

rnf :: RestoreRequest -> () #

type Rep RestoreRequest Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

restoreRequest :: RestoreRequest Source #

Creates a value of RestoreRequest with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • rrDays - Lifetime of the active copy in days. Do not use with restores that specify OutputLocation.
  • rrSelectParameters - Describes the parameters for Select job types.
  • rrOutputLocation - Describes the location where the restore job's output is stored.
  • rrTier - Glacier retrieval tier at which the restore will be processed.
  • rrGlacierJobParameters - Glacier related parameters pertaining to this job. Do not use with restores that specify OutputLocation.
  • rrType - Type of restore request.
  • rrDescription - The optional description for the job.

rrDays :: Lens' RestoreRequest (Maybe Int) Source #

Lifetime of the active copy in days. Do not use with restores that specify OutputLocation.

rrSelectParameters :: Lens' RestoreRequest (Maybe SelectParameters) Source #

Describes the parameters for Select job types.

rrOutputLocation :: Lens' RestoreRequest (Maybe OutputLocation) Source #

Describes the location where the restore job's output is stored.

rrTier :: Lens' RestoreRequest (Maybe Tier) Source #

Glacier retrieval tier at which the restore will be processed.

rrGlacierJobParameters :: Lens' RestoreRequest (Maybe GlacierJobParameters) Source #

Glacier related parameters pertaining to this job. Do not use with restores that specify OutputLocation.

rrDescription :: Lens' RestoreRequest (Maybe Text) Source #

The optional description for the job.

RoutingRule

data RoutingRule Source #

See: routingRule smart constructor.

Instances
Eq RoutingRule Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Data RoutingRule Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RoutingRule -> c RoutingRule #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RoutingRule #

toConstr :: RoutingRule -> Constr #

dataTypeOf :: RoutingRule -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c RoutingRule) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RoutingRule) #

gmapT :: (forall b. Data b => b -> b) -> RoutingRule -> RoutingRule #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RoutingRule -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RoutingRule -> r #

gmapQ :: (forall d. Data d => d -> u) -> RoutingRule -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RoutingRule -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RoutingRule -> m RoutingRule #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RoutingRule -> m RoutingRule #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RoutingRule -> m RoutingRule #

Read RoutingRule Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Show RoutingRule Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Generic RoutingRule Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Associated Types

type Rep RoutingRule :: Type -> Type #

Hashable RoutingRule Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

FromXML RoutingRule Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

ToXML RoutingRule Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

toXML :: RoutingRule -> XML #

NFData RoutingRule Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

rnf :: RoutingRule -> () #

type Rep RoutingRule Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

type Rep RoutingRule = D1 (MetaData "RoutingRule" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" False) (C1 (MetaCons "RoutingRule'" PrefixI True) (S1 (MetaSel (Just "_rrCondition") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Condition)) :*: S1 (MetaSel (Just "_rrRedirect") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Redirect)))

routingRule Source #

Creates a value of RoutingRule with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • rrCondition - A container for describing a condition that must be met for the specified redirect to apply. For example, 1. If request is for pages in the docs folder, redirect to the documents folder. 2. If request results in HTTP error 4xx, redirect request to another host where you might process the error.
  • rrRedirect - Container for redirect information. You can redirect requests to another host, to another page, or with another protocol. In the event of an error, you can can specify a different error code to return.

rrCondition :: Lens' RoutingRule (Maybe Condition) Source #

A container for describing a condition that must be met for the specified redirect to apply. For example, 1. If request is for pages in the docs folder, redirect to the documents folder. 2. If request results in HTTP error 4xx, redirect request to another host where you might process the error.

rrRedirect :: Lens' RoutingRule Redirect Source #

Container for redirect information. You can redirect requests to another host, to another page, or with another protocol. In the event of an error, you can can specify a different error code to return.

S3KeyFilter

data S3KeyFilter Source #

Container for object key name prefix and suffix filtering rules.

See: s3KeyFilter smart constructor.

Instances
Eq S3KeyFilter Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Data S3KeyFilter Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> S3KeyFilter -> c S3KeyFilter #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c S3KeyFilter #

toConstr :: S3KeyFilter -> Constr #

dataTypeOf :: S3KeyFilter -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c S3KeyFilter) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c S3KeyFilter) #

gmapT :: (forall b. Data b => b -> b) -> S3KeyFilter -> S3KeyFilter #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> S3KeyFilter -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> S3KeyFilter -> r #

gmapQ :: (forall d. Data d => d -> u) -> S3KeyFilter -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> S3KeyFilter -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> S3KeyFilter -> m S3KeyFilter #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> S3KeyFilter -> m S3KeyFilter #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> S3KeyFilter -> m S3KeyFilter #

Read S3KeyFilter Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Show S3KeyFilter Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Generic S3KeyFilter Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Associated Types

type Rep S3KeyFilter :: Type -> Type #

Hashable S3KeyFilter Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

FromXML S3KeyFilter Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

ToXML S3KeyFilter Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

toXML :: S3KeyFilter -> XML #

NFData S3KeyFilter Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

rnf :: S3KeyFilter -> () #

type Rep S3KeyFilter Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

type Rep S3KeyFilter = D1 (MetaData "S3KeyFilter" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" True) (C1 (MetaCons "S3KeyFilter'" PrefixI True) (S1 (MetaSel (Just "_skfFilterRules") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe [FilterRule]))))

s3KeyFilter :: S3KeyFilter Source #

Creates a value of S3KeyFilter with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

S3Location

data S3Location Source #

Describes an S3 location that will receive the results of the restore request.

See: s3Location smart constructor.

Instances
Eq S3Location Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Data S3Location Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> S3Location -> c S3Location #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c S3Location #

toConstr :: S3Location -> Constr #

dataTypeOf :: S3Location -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c S3Location) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c S3Location) #

gmapT :: (forall b. Data b => b -> b) -> S3Location -> S3Location #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> S3Location -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> S3Location -> r #

gmapQ :: (forall d. Data d => d -> u) -> S3Location -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> S3Location -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> S3Location -> m S3Location #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> S3Location -> m S3Location #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> S3Location -> m S3Location #

Show S3Location Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Generic S3Location Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Associated Types

type Rep S3Location :: Type -> Type #

Hashable S3Location Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

ToXML S3Location Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

toXML :: S3Location -> XML #

NFData S3Location Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

rnf :: S3Location -> () #

type Rep S3Location Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

s3Location Source #

Creates a value of S3Location with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • slCannedACL - The canned ACL to apply to the restore results.
  • slAccessControlList - A list of grants that control access to the staged results.
  • slUserMetadata - A list of metadata to store with the restore results in S3.
  • slEncryption - Undocumented member.
  • slStorageClass - The class of storage used to store the restore results.
  • slTagging - The tag-set that is applied to the restore results.
  • slBucketName - The name of the bucket where the restore results will be placed.
  • slPrefix - The prefix that is prepended to the restore results for this request.

slCannedACL :: Lens' S3Location (Maybe ObjectCannedACL) Source #

The canned ACL to apply to the restore results.

slAccessControlList :: Lens' S3Location [Grant] Source #

A list of grants that control access to the staged results.

slUserMetadata :: Lens' S3Location [MetadataEntry] Source #

A list of metadata to store with the restore results in S3.

slStorageClass :: Lens' S3Location (Maybe StorageClass) Source #

The class of storage used to store the restore results.

slTagging :: Lens' S3Location (Maybe Tagging) Source #

The tag-set that is applied to the restore results.

slBucketName :: Lens' S3Location BucketName Source #

The name of the bucket where the restore results will be placed.

slPrefix :: Lens' S3Location Text Source #

The prefix that is prepended to the restore results for this request.

S3ServiceError

data S3ServiceError Source #

See: s3ServiceError smart constructor.

Instances
Eq S3ServiceError Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Data S3ServiceError Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> S3ServiceError -> c S3ServiceError #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c S3ServiceError #

toConstr :: S3ServiceError -> Constr #

dataTypeOf :: S3ServiceError -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c S3ServiceError) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c S3ServiceError) #

gmapT :: (forall b. Data b => b -> b) -> S3ServiceError -> S3ServiceError #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> S3ServiceError -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> S3ServiceError -> r #

gmapQ :: (forall d. Data d => d -> u) -> S3ServiceError -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> S3ServiceError -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> S3ServiceError -> m S3ServiceError #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> S3ServiceError -> m S3ServiceError #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> S3ServiceError -> m S3ServiceError #

Read S3ServiceError Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Show S3ServiceError Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Generic S3ServiceError Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Associated Types

type Rep S3ServiceError :: Type -> Type #

Hashable S3ServiceError Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

FromXML S3ServiceError Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

NFData S3ServiceError Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

rnf :: S3ServiceError -> () #

type Rep S3ServiceError Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

type Rep S3ServiceError = D1 (MetaData "S3ServiceError" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" False) (C1 (MetaCons "S3ServiceError'" PrefixI True) ((S1 (MetaSel (Just "_sseVersionId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ObjectVersionId)) :*: S1 (MetaSel (Just "_sseKey") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ObjectKey))) :*: (S1 (MetaSel (Just "_sseCode") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_sseMessage") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))

s3ServiceError :: S3ServiceError Source #

Creates a value of S3ServiceError with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

sseKey :: Lens' S3ServiceError (Maybe ObjectKey) Source #

Undocumented member.

sseCode :: Lens' S3ServiceError (Maybe Text) Source #

Undocumented member.

sseMessage :: Lens' S3ServiceError (Maybe Text) Source #

Undocumented member.

SSEKMS

data SSEKMS Source #

Specifies the use of SSE-KMS to encrypt delievered Inventory reports.

See: sSEKMS smart constructor.

Instances
Eq SSEKMS Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

(==) :: SSEKMS -> SSEKMS -> Bool #

(/=) :: SSEKMS -> SSEKMS -> Bool #

Data SSEKMS Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SSEKMS -> c SSEKMS #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SSEKMS #

toConstr :: SSEKMS -> Constr #

dataTypeOf :: SSEKMS -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SSEKMS) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SSEKMS) #

gmapT :: (forall b. Data b => b -> b) -> SSEKMS -> SSEKMS #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SSEKMS -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SSEKMS -> r #

gmapQ :: (forall d. Data d => d -> u) -> SSEKMS -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SSEKMS -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SSEKMS -> m SSEKMS #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SSEKMS -> m SSEKMS #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SSEKMS -> m SSEKMS #

Show SSEKMS Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Generic SSEKMS Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Associated Types

type Rep SSEKMS :: Type -> Type #

Methods

from :: SSEKMS -> Rep SSEKMS x #

to :: Rep SSEKMS x -> SSEKMS #

Hashable SSEKMS Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

hashWithSalt :: Int -> SSEKMS -> Int #

hash :: SSEKMS -> Int #

FromXML SSEKMS Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

ToXML SSEKMS Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

toXML :: SSEKMS -> XML #

NFData SSEKMS Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

rnf :: SSEKMS -> () #

type Rep SSEKMS Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

type Rep SSEKMS = D1 (MetaData "SSEKMS" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" True) (C1 (MetaCons "SSEKMS'" PrefixI True) (S1 (MetaSel (Just "_ssekKeyId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Sensitive Text))))

sSEKMS Source #

Arguments

:: Text

ssekKeyId

-> SSEKMS 

Creates a value of SSEKMS with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • ssekKeyId - Specifies the ID of the AWS Key Management Service (KMS) master encryption key to use for encrypting Inventory reports.

ssekKeyId :: Lens' SSEKMS Text Source #

Specifies the ID of the AWS Key Management Service (KMS) master encryption key to use for encrypting Inventory reports.

SSES3

data SSES3 Source #

Specifies the use of SSE-S3 to encrypt delievered Inventory reports.

See: sSES3 smart constructor.

Instances
Eq SSES3 Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

(==) :: SSES3 -> SSES3 -> Bool #

(/=) :: SSES3 -> SSES3 -> Bool #

Data SSES3 Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SSES3 -> c SSES3 #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SSES3 #

toConstr :: SSES3 -> Constr #

dataTypeOf :: SSES3 -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SSES3) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SSES3) #

gmapT :: (forall b. Data b => b -> b) -> SSES3 -> SSES3 #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SSES3 -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SSES3 -> r #

gmapQ :: (forall d. Data d => d -> u) -> SSES3 -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SSES3 -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SSES3 -> m SSES3 #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SSES3 -> m SSES3 #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SSES3 -> m SSES3 #

Read SSES3 Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Show SSES3 Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

showsPrec :: Int -> SSES3 -> ShowS #

show :: SSES3 -> String #

showList :: [SSES3] -> ShowS #

Generic SSES3 Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Associated Types

type Rep SSES3 :: Type -> Type #

Methods

from :: SSES3 -> Rep SSES3 x #

to :: Rep SSES3 x -> SSES3 #

Hashable SSES3 Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

hashWithSalt :: Int -> SSES3 -> Int #

hash :: SSES3 -> Int #

FromXML SSES3 Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

parseXML :: [Node] -> Either String SSES3 #

ToXML SSES3 Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

toXML :: SSES3 -> XML #

NFData SSES3 Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

rnf :: SSES3 -> () #

type Rep SSES3 Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

type Rep SSES3 = D1 (MetaData "SSES3" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" False) (C1 (MetaCons "SSES3'" PrefixI False) (U1 :: Type -> Type))

sSES3 :: SSES3 Source #

Creates a value of SSES3 with the minimum fields required to make a request.

SelectObjectContentEventStream

data SelectObjectContentEventStream Source #

See: selectObjectContentEventStream smart constructor.

Instances
Eq SelectObjectContentEventStream Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Data SelectObjectContentEventStream Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SelectObjectContentEventStream -> c SelectObjectContentEventStream #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SelectObjectContentEventStream #

toConstr :: SelectObjectContentEventStream -> Constr #

dataTypeOf :: SelectObjectContentEventStream -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SelectObjectContentEventStream) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SelectObjectContentEventStream) #

gmapT :: (forall b. Data b => b -> b) -> SelectObjectContentEventStream -> SelectObjectContentEventStream #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SelectObjectContentEventStream -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SelectObjectContentEventStream -> r #

gmapQ :: (forall d. Data d => d -> u) -> SelectObjectContentEventStream -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SelectObjectContentEventStream -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SelectObjectContentEventStream -> m SelectObjectContentEventStream #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SelectObjectContentEventStream -> m SelectObjectContentEventStream #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SelectObjectContentEventStream -> m SelectObjectContentEventStream #

Read SelectObjectContentEventStream Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Show SelectObjectContentEventStream Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Generic SelectObjectContentEventStream Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Associated Types

type Rep SelectObjectContentEventStream :: Type -> Type #

Hashable SelectObjectContentEventStream Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

FromXML SelectObjectContentEventStream Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

NFData SelectObjectContentEventStream Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

type Rep SelectObjectContentEventStream Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

type Rep SelectObjectContentEventStream = D1 (MetaData "SelectObjectContentEventStream" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" False) (C1 (MetaCons "SelectObjectContentEventStream'" PrefixI True) ((S1 (MetaSel (Just "_socesProgress") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ProgressEvent)) :*: S1 (MetaSel (Just "_socesRecords") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe RecordsEvent))) :*: (S1 (MetaSel (Just "_socesCont") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ContinuationEvent)) :*: (S1 (MetaSel (Just "_socesStats") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe StatsEvent)) :*: S1 (MetaSel (Just "_socesEnd") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe EndEvent))))))

selectObjectContentEventStream :: SelectObjectContentEventStream Source #

Creates a value of SelectObjectContentEventStream with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

SelectParameters

data SelectParameters Source #

Describes the parameters for Select job types.

See: selectParameters smart constructor.

Instances
Eq SelectParameters Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Data SelectParameters Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SelectParameters -> c SelectParameters #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SelectParameters #

toConstr :: SelectParameters -> Constr #

dataTypeOf :: SelectParameters -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SelectParameters) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SelectParameters) #

gmapT :: (forall b. Data b => b -> b) -> SelectParameters -> SelectParameters #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SelectParameters -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SelectParameters -> r #

gmapQ :: (forall d. Data d => d -> u) -> SelectParameters -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SelectParameters -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SelectParameters -> m SelectParameters #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SelectParameters -> m SelectParameters #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SelectParameters -> m SelectParameters #

Read SelectParameters Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Show SelectParameters Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Generic SelectParameters Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Associated Types

type Rep SelectParameters :: Type -> Type #

Hashable SelectParameters Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

ToXML SelectParameters Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

NFData SelectParameters Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

rnf :: SelectParameters -> () #

type Rep SelectParameters Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

type Rep SelectParameters = D1 (MetaData "SelectParameters" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" False) (C1 (MetaCons "SelectParameters'" PrefixI True) ((S1 (MetaSel (Just "_spInputSerialization") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 InputSerialization) :*: S1 (MetaSel (Just "_spExpressionType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 ExpressionType)) :*: (S1 (MetaSel (Just "_spExpression") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text) :*: S1 (MetaSel (Just "_spOutputSerialization") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 OutputSerialization))))

selectParameters Source #

Creates a value of SelectParameters with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

spInputSerialization :: Lens' SelectParameters InputSerialization Source #

Describes the serialization format of the object.

spExpressionType :: Lens' SelectParameters ExpressionType Source #

The type of the provided expression (e.g., SQL).

spExpression :: Lens' SelectParameters Text Source #

The expression that is used to query the object.

spOutputSerialization :: Lens' SelectParameters OutputSerialization Source #

Describes how the results of the Select job are serialized.

ServerSideEncryptionByDefault

data ServerSideEncryptionByDefault Source #

Describes the default server-side encryption to apply to new objects in the bucket. If Put Object request does not specify any server-side encryption, this default encryption will be applied.

See: serverSideEncryptionByDefault smart constructor.

Instances
Eq ServerSideEncryptionByDefault Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Data ServerSideEncryptionByDefault Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ServerSideEncryptionByDefault -> c ServerSideEncryptionByDefault #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ServerSideEncryptionByDefault #

toConstr :: ServerSideEncryptionByDefault -> Constr #

dataTypeOf :: ServerSideEncryptionByDefault -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ServerSideEncryptionByDefault) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ServerSideEncryptionByDefault) #

gmapT :: (forall b. Data b => b -> b) -> ServerSideEncryptionByDefault -> ServerSideEncryptionByDefault #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ServerSideEncryptionByDefault -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ServerSideEncryptionByDefault -> r #

gmapQ :: (forall d. Data d => d -> u) -> ServerSideEncryptionByDefault -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ServerSideEncryptionByDefault -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ServerSideEncryptionByDefault -> m ServerSideEncryptionByDefault #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ServerSideEncryptionByDefault -> m ServerSideEncryptionByDefault #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ServerSideEncryptionByDefault -> m ServerSideEncryptionByDefault #

Show ServerSideEncryptionByDefault Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Generic ServerSideEncryptionByDefault Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Associated Types

type Rep ServerSideEncryptionByDefault :: Type -> Type #

Hashable ServerSideEncryptionByDefault Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

FromXML ServerSideEncryptionByDefault Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

ToXML ServerSideEncryptionByDefault Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

NFData ServerSideEncryptionByDefault Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

type Rep ServerSideEncryptionByDefault Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

type Rep ServerSideEncryptionByDefault = D1 (MetaData "ServerSideEncryptionByDefault" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" False) (C1 (MetaCons "ServerSideEncryptionByDefault'" PrefixI True) (S1 (MetaSel (Just "_ssebdKMSMasterKeyId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Sensitive Text))) :*: S1 (MetaSel (Just "_ssebdSSEAlgorithm") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 ServerSideEncryption)))

serverSideEncryptionByDefault Source #

Creates a value of ServerSideEncryptionByDefault with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • ssebdKMSMasterKeyId - KMS master key ID to use for the default encryption. This parameter is allowed if SSEAlgorithm is aws:kms.
  • ssebdSSEAlgorithm - Server-side encryption algorithm to use for the default encryption.

ssebdKMSMasterKeyId :: Lens' ServerSideEncryptionByDefault (Maybe Text) Source #

KMS master key ID to use for the default encryption. This parameter is allowed if SSEAlgorithm is aws:kms.

ssebdSSEAlgorithm :: Lens' ServerSideEncryptionByDefault ServerSideEncryption Source #

Server-side encryption algorithm to use for the default encryption.

ServerSideEncryptionConfiguration

data ServerSideEncryptionConfiguration Source #

Container for server-side encryption configuration rules. Currently S3 supports one rule only.

See: serverSideEncryptionConfiguration smart constructor.

Instances
Eq ServerSideEncryptionConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Data ServerSideEncryptionConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ServerSideEncryptionConfiguration -> c ServerSideEncryptionConfiguration #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ServerSideEncryptionConfiguration #

toConstr :: ServerSideEncryptionConfiguration -> Constr #

dataTypeOf :: ServerSideEncryptionConfiguration -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ServerSideEncryptionConfiguration) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ServerSideEncryptionConfiguration) #

gmapT :: (forall b. Data b => b -> b) -> ServerSideEncryptionConfiguration -> ServerSideEncryptionConfiguration #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ServerSideEncryptionConfiguration -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ServerSideEncryptionConfiguration -> r #

gmapQ :: (forall d. Data d => d -> u) -> ServerSideEncryptionConfiguration -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ServerSideEncryptionConfiguration -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ServerSideEncryptionConfiguration -> m ServerSideEncryptionConfiguration #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ServerSideEncryptionConfiguration -> m ServerSideEncryptionConfiguration #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ServerSideEncryptionConfiguration -> m ServerSideEncryptionConfiguration #

Show ServerSideEncryptionConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Generic ServerSideEncryptionConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Associated Types

type Rep ServerSideEncryptionConfiguration :: Type -> Type #

Hashable ServerSideEncryptionConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

FromXML ServerSideEncryptionConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

ToXML ServerSideEncryptionConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

NFData ServerSideEncryptionConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

type Rep ServerSideEncryptionConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

type Rep ServerSideEncryptionConfiguration = D1 (MetaData "ServerSideEncryptionConfiguration" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" True) (C1 (MetaCons "ServerSideEncryptionConfiguration'" PrefixI True) (S1 (MetaSel (Just "_ssecRules") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [ServerSideEncryptionRule])))

serverSideEncryptionConfiguration :: ServerSideEncryptionConfiguration Source #

Creates a value of ServerSideEncryptionConfiguration with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • ssecRules - Container for information about a particular server-side encryption configuration rule.

ssecRules :: Lens' ServerSideEncryptionConfiguration [ServerSideEncryptionRule] Source #

Container for information about a particular server-side encryption configuration rule.

ServerSideEncryptionRule

data ServerSideEncryptionRule Source #

Container for information about a particular server-side encryption configuration rule.

See: serverSideEncryptionRule smart constructor.

Instances
Eq ServerSideEncryptionRule Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Data ServerSideEncryptionRule Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ServerSideEncryptionRule -> c ServerSideEncryptionRule #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ServerSideEncryptionRule #

toConstr :: ServerSideEncryptionRule -> Constr #

dataTypeOf :: ServerSideEncryptionRule -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ServerSideEncryptionRule) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ServerSideEncryptionRule) #

gmapT :: (forall b. Data b => b -> b) -> ServerSideEncryptionRule -> ServerSideEncryptionRule #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ServerSideEncryptionRule -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ServerSideEncryptionRule -> r #

gmapQ :: (forall d. Data d => d -> u) -> ServerSideEncryptionRule -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ServerSideEncryptionRule -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ServerSideEncryptionRule -> m ServerSideEncryptionRule #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ServerSideEncryptionRule -> m ServerSideEncryptionRule #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ServerSideEncryptionRule -> m ServerSideEncryptionRule #

Show ServerSideEncryptionRule Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Generic ServerSideEncryptionRule Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Associated Types

type Rep ServerSideEncryptionRule :: Type -> Type #

Hashable ServerSideEncryptionRule Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

FromXML ServerSideEncryptionRule Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

ToXML ServerSideEncryptionRule Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

NFData ServerSideEncryptionRule Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

type Rep ServerSideEncryptionRule Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

type Rep ServerSideEncryptionRule = D1 (MetaData "ServerSideEncryptionRule" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" True) (C1 (MetaCons "ServerSideEncryptionRule'" PrefixI True) (S1 (MetaSel (Just "_sserApplyServerSideEncryptionByDefault") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe ServerSideEncryptionByDefault))))

serverSideEncryptionRule :: ServerSideEncryptionRule Source #

Creates a value of ServerSideEncryptionRule with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • sserApplyServerSideEncryptionByDefault - Describes the default server-side encryption to apply to new objects in the bucket. If Put Object request does not specify any server-side encryption, this default encryption will be applied.

sserApplyServerSideEncryptionByDefault :: Lens' ServerSideEncryptionRule (Maybe ServerSideEncryptionByDefault) Source #

Describes the default server-side encryption to apply to new objects in the bucket. If Put Object request does not specify any server-side encryption, this default encryption will be applied.

SourceSelectionCriteria

data SourceSelectionCriteria Source #

Container for filters that define which source objects should be replicated.

See: sourceSelectionCriteria smart constructor.

Instances
Eq SourceSelectionCriteria Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Data SourceSelectionCriteria Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SourceSelectionCriteria -> c SourceSelectionCriteria #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SourceSelectionCriteria #

toConstr :: SourceSelectionCriteria -> Constr #

dataTypeOf :: SourceSelectionCriteria -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SourceSelectionCriteria) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SourceSelectionCriteria) #

gmapT :: (forall b. Data b => b -> b) -> SourceSelectionCriteria -> SourceSelectionCriteria #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SourceSelectionCriteria -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SourceSelectionCriteria -> r #

gmapQ :: (forall d. Data d => d -> u) -> SourceSelectionCriteria -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SourceSelectionCriteria -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SourceSelectionCriteria -> m SourceSelectionCriteria #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SourceSelectionCriteria -> m SourceSelectionCriteria #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SourceSelectionCriteria -> m SourceSelectionCriteria #

Read SourceSelectionCriteria Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Show SourceSelectionCriteria Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Generic SourceSelectionCriteria Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Associated Types

type Rep SourceSelectionCriteria :: Type -> Type #

Hashable SourceSelectionCriteria Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

FromXML SourceSelectionCriteria Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

ToXML SourceSelectionCriteria Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

NFData SourceSelectionCriteria Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

rnf :: SourceSelectionCriteria -> () #

type Rep SourceSelectionCriteria Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

type Rep SourceSelectionCriteria = D1 (MetaData "SourceSelectionCriteria" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" True) (C1 (MetaCons "SourceSelectionCriteria'" PrefixI True) (S1 (MetaSel (Just "_sscSseKMSEncryptedObjects") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe SseKMSEncryptedObjects))))

sourceSelectionCriteria :: SourceSelectionCriteria Source #

Creates a value of SourceSelectionCriteria with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

sscSseKMSEncryptedObjects :: Lens' SourceSelectionCriteria (Maybe SseKMSEncryptedObjects) Source #

Container for filter information of selection of KMS Encrypted S3 objects.

SseKMSEncryptedObjects

data SseKMSEncryptedObjects Source #

Container for filter information of selection of KMS Encrypted S3 objects.

See: sseKMSEncryptedObjects smart constructor.

Instances
Eq SseKMSEncryptedObjects Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Data SseKMSEncryptedObjects Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SseKMSEncryptedObjects -> c SseKMSEncryptedObjects #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SseKMSEncryptedObjects #

toConstr :: SseKMSEncryptedObjects -> Constr #

dataTypeOf :: SseKMSEncryptedObjects -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SseKMSEncryptedObjects) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SseKMSEncryptedObjects) #

gmapT :: (forall b. Data b => b -> b) -> SseKMSEncryptedObjects -> SseKMSEncryptedObjects #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SseKMSEncryptedObjects -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SseKMSEncryptedObjects -> r #

gmapQ :: (forall d. Data d => d -> u) -> SseKMSEncryptedObjects -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SseKMSEncryptedObjects -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SseKMSEncryptedObjects -> m SseKMSEncryptedObjects #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SseKMSEncryptedObjects -> m SseKMSEncryptedObjects #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SseKMSEncryptedObjects -> m SseKMSEncryptedObjects #

Read SseKMSEncryptedObjects Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Show SseKMSEncryptedObjects Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Generic SseKMSEncryptedObjects Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Associated Types

type Rep SseKMSEncryptedObjects :: Type -> Type #

Hashable SseKMSEncryptedObjects Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

FromXML SseKMSEncryptedObjects Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

ToXML SseKMSEncryptedObjects Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

NFData SseKMSEncryptedObjects Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

rnf :: SseKMSEncryptedObjects -> () #

type Rep SseKMSEncryptedObjects Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

type Rep SseKMSEncryptedObjects = D1 (MetaData "SseKMSEncryptedObjects" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" True) (C1 (MetaCons "SseKMSEncryptedObjects'" PrefixI True) (S1 (MetaSel (Just "_skeoStatus") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SseKMSEncryptedObjectsStatus)))

sseKMSEncryptedObjects Source #

Creates a value of SseKMSEncryptedObjects with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • skeoStatus - The replication for KMS encrypted S3 objects is disabled if status is not Enabled.

skeoStatus :: Lens' SseKMSEncryptedObjects SseKMSEncryptedObjectsStatus Source #

The replication for KMS encrypted S3 objects is disabled if status is not Enabled.

Stats

data Stats Source #

See: stats smart constructor.

Instances
Eq Stats Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

(==) :: Stats -> Stats -> Bool #

(/=) :: Stats -> Stats -> Bool #

Data Stats Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Stats -> c Stats #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Stats #

toConstr :: Stats -> Constr #

dataTypeOf :: Stats -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Stats) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Stats) #

gmapT :: (forall b. Data b => b -> b) -> Stats -> Stats #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Stats -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Stats -> r #

gmapQ :: (forall d. Data d => d -> u) -> Stats -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Stats -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Stats -> m Stats #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Stats -> m Stats #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Stats -> m Stats #

Read Stats Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Show Stats Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

showsPrec :: Int -> Stats -> ShowS #

show :: Stats -> String #

showList :: [Stats] -> ShowS #

Generic Stats Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Associated Types

type Rep Stats :: Type -> Type #

Methods

from :: Stats -> Rep Stats x #

to :: Rep Stats x -> Stats #

Hashable Stats Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

hashWithSalt :: Int -> Stats -> Int #

hash :: Stats -> Int #

FromXML Stats Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

parseXML :: [Node] -> Either String Stats #

NFData Stats Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

rnf :: Stats -> () #

type Rep Stats Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

type Rep Stats = D1 (MetaData "Stats" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" False) (C1 (MetaCons "Stats'" PrefixI True) (S1 (MetaSel (Just "_sBytesReturned") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Integer)) :*: (S1 (MetaSel (Just "_sBytesScanned") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Integer)) :*: S1 (MetaSel (Just "_sBytesProcessed") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Integer)))))

stats :: Stats Source #

Creates a value of Stats with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

sBytesReturned :: Lens' Stats (Maybe Integer) Source #

Total number of bytes of records payload data returned.

sBytesScanned :: Lens' Stats (Maybe Integer) Source #

Total number of object bytes scanned.

sBytesProcessed :: Lens' Stats (Maybe Integer) Source #

Total number of uncompressed object bytes processed.

StatsEvent

data StatsEvent Source #

See: statsEvent smart constructor.

Instances
Eq StatsEvent Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Data StatsEvent Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> StatsEvent -> c StatsEvent #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c StatsEvent #

toConstr :: StatsEvent -> Constr #

dataTypeOf :: StatsEvent -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c StatsEvent) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c StatsEvent) #

gmapT :: (forall b. Data b => b -> b) -> StatsEvent -> StatsEvent #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> StatsEvent -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> StatsEvent -> r #

gmapQ :: (forall d. Data d => d -> u) -> StatsEvent -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> StatsEvent -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> StatsEvent -> m StatsEvent #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> StatsEvent -> m StatsEvent #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> StatsEvent -> m StatsEvent #

Read StatsEvent Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Show StatsEvent Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Generic StatsEvent Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Associated Types

type Rep StatsEvent :: Type -> Type #

Hashable StatsEvent Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

FromXML StatsEvent Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

NFData StatsEvent Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

rnf :: StatsEvent -> () #

type Rep StatsEvent Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

type Rep StatsEvent = D1 (MetaData "StatsEvent" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" True) (C1 (MetaCons "StatsEvent'" PrefixI True) (S1 (MetaSel (Just "_seDetails") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Stats))))

statsEvent :: StatsEvent Source #

Creates a value of StatsEvent with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

seDetails :: Lens' StatsEvent (Maybe Stats) Source #

The Stats event details.

StorageClassAnalysis

data StorageClassAnalysis Source #

See: storageClassAnalysis smart constructor.

Instances
Eq StorageClassAnalysis Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Data StorageClassAnalysis Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> StorageClassAnalysis -> c StorageClassAnalysis #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c StorageClassAnalysis #

toConstr :: StorageClassAnalysis -> Constr #

dataTypeOf :: StorageClassAnalysis -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c StorageClassAnalysis) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c StorageClassAnalysis) #

gmapT :: (forall b. Data b => b -> b) -> StorageClassAnalysis -> StorageClassAnalysis #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> StorageClassAnalysis -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> StorageClassAnalysis -> r #

gmapQ :: (forall d. Data d => d -> u) -> StorageClassAnalysis -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> StorageClassAnalysis -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> StorageClassAnalysis -> m StorageClassAnalysis #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> StorageClassAnalysis -> m StorageClassAnalysis #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> StorageClassAnalysis -> m StorageClassAnalysis #

Read StorageClassAnalysis Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Show StorageClassAnalysis Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Generic StorageClassAnalysis Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Associated Types

type Rep StorageClassAnalysis :: Type -> Type #

Hashable StorageClassAnalysis Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

FromXML StorageClassAnalysis Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

ToXML StorageClassAnalysis Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

NFData StorageClassAnalysis Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

rnf :: StorageClassAnalysis -> () #

type Rep StorageClassAnalysis Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

type Rep StorageClassAnalysis = D1 (MetaData "StorageClassAnalysis" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" True) (C1 (MetaCons "StorageClassAnalysis'" PrefixI True) (S1 (MetaSel (Just "_scaDataExport") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe StorageClassAnalysisDataExport))))

storageClassAnalysis :: StorageClassAnalysis Source #

Creates a value of StorageClassAnalysis with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • scaDataExport - A container used to describe how data related to the storage class analysis should be exported.

scaDataExport :: Lens' StorageClassAnalysis (Maybe StorageClassAnalysisDataExport) Source #

A container used to describe how data related to the storage class analysis should be exported.

StorageClassAnalysisDataExport

data StorageClassAnalysisDataExport Source #

See: storageClassAnalysisDataExport smart constructor.

Instances
Eq StorageClassAnalysisDataExport Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Data StorageClassAnalysisDataExport Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> StorageClassAnalysisDataExport -> c StorageClassAnalysisDataExport #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c StorageClassAnalysisDataExport #

toConstr :: StorageClassAnalysisDataExport -> Constr #

dataTypeOf :: StorageClassAnalysisDataExport -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c StorageClassAnalysisDataExport) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c StorageClassAnalysisDataExport) #

gmapT :: (forall b. Data b => b -> b) -> StorageClassAnalysisDataExport -> StorageClassAnalysisDataExport #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> StorageClassAnalysisDataExport -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> StorageClassAnalysisDataExport -> r #

gmapQ :: (forall d. Data d => d -> u) -> StorageClassAnalysisDataExport -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> StorageClassAnalysisDataExport -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> StorageClassAnalysisDataExport -> m StorageClassAnalysisDataExport #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> StorageClassAnalysisDataExport -> m StorageClassAnalysisDataExport #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> StorageClassAnalysisDataExport -> m StorageClassAnalysisDataExport #

Read StorageClassAnalysisDataExport Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Show StorageClassAnalysisDataExport Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Generic StorageClassAnalysisDataExport Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Associated Types

type Rep StorageClassAnalysisDataExport :: Type -> Type #

Hashable StorageClassAnalysisDataExport Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

FromXML StorageClassAnalysisDataExport Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

ToXML StorageClassAnalysisDataExport Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

NFData StorageClassAnalysisDataExport Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

type Rep StorageClassAnalysisDataExport Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

type Rep StorageClassAnalysisDataExport = D1 (MetaData "StorageClassAnalysisDataExport" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" False) (C1 (MetaCons "StorageClassAnalysisDataExport'" PrefixI True) (S1 (MetaSel (Just "_scadeOutputSchemaVersion") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 StorageClassAnalysisSchemaVersion) :*: S1 (MetaSel (Just "_scadeDestination") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 AnalyticsExportDestination)))

storageClassAnalysisDataExport Source #

Creates a value of StorageClassAnalysisDataExport with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

scadeOutputSchemaVersion :: Lens' StorageClassAnalysisDataExport StorageClassAnalysisSchemaVersion Source #

The version of the output schema to use when exporting data. Must be V_1.

Tag

data Tag Source #

See: tag smart constructor.

Instances
Eq Tag Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

(==) :: Tag -> Tag -> Bool #

(/=) :: Tag -> Tag -> Bool #

Data Tag Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Tag -> c Tag #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Tag #

toConstr :: Tag -> Constr #

dataTypeOf :: Tag -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Tag) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Tag) #

gmapT :: (forall b. Data b => b -> b) -> Tag -> Tag #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Tag -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Tag -> r #

gmapQ :: (forall d. Data d => d -> u) -> Tag -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Tag -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Tag -> m Tag #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Tag -> m Tag #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Tag -> m Tag #

Read Tag Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Show Tag Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

showsPrec :: Int -> Tag -> ShowS #

show :: Tag -> String #

showList :: [Tag] -> ShowS #

Generic Tag Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Associated Types

type Rep Tag :: Type -> Type #

Methods

from :: Tag -> Rep Tag x #

to :: Rep Tag x -> Tag #

Hashable Tag Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

hashWithSalt :: Int -> Tag -> Int #

hash :: Tag -> Int #

FromXML Tag Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

parseXML :: [Node] -> Either String Tag #

ToXML Tag Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

toXML :: Tag -> XML #

NFData Tag Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

rnf :: Tag -> () #

type Rep Tag Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

type Rep Tag = D1 (MetaData "Tag" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" False) (C1 (MetaCons "Tag'" PrefixI True) (S1 (MetaSel (Just "_tagKey") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 ObjectKey) :*: S1 (MetaSel (Just "_tagValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)))

tag Source #

Arguments

:: ObjectKey

tagKey

-> Text

tagValue

-> Tag 

Creates a value of Tag with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

tagKey :: Lens' Tag ObjectKey Source #

Name of the tag.

tagValue :: Lens' Tag Text Source #

Value of the tag.

Tagging

data Tagging Source #

See: tagging smart constructor.

Instances
Eq Tagging Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

(==) :: Tagging -> Tagging -> Bool #

(/=) :: Tagging -> Tagging -> Bool #

Data Tagging Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Tagging -> c Tagging #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Tagging #

toConstr :: Tagging -> Constr #

dataTypeOf :: Tagging -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Tagging) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Tagging) #

gmapT :: (forall b. Data b => b -> b) -> Tagging -> Tagging #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Tagging -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Tagging -> r #

gmapQ :: (forall d. Data d => d -> u) -> Tagging -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Tagging -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Tagging -> m Tagging #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Tagging -> m Tagging #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Tagging -> m Tagging #

Read Tagging Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Show Tagging Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Generic Tagging Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Associated Types

type Rep Tagging :: Type -> Type #

Methods

from :: Tagging -> Rep Tagging x #

to :: Rep Tagging x -> Tagging #

Hashable Tagging Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

hashWithSalt :: Int -> Tagging -> Int #

hash :: Tagging -> Int #

ToXML Tagging Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

toXML :: Tagging -> XML #

NFData Tagging Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

rnf :: Tagging -> () #

type Rep Tagging Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

type Rep Tagging = D1 (MetaData "Tagging" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" True) (C1 (MetaCons "Tagging'" PrefixI True) (S1 (MetaSel (Just "_tTagSet") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Tag])))

tagging :: Tagging Source #

Creates a value of Tagging with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

tTagSet :: Lens' Tagging [Tag] Source #

Undocumented member.

TargetGrant

data TargetGrant Source #

See: targetGrant smart constructor.

Instances
Eq TargetGrant Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Data TargetGrant Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TargetGrant -> c TargetGrant #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TargetGrant #

toConstr :: TargetGrant -> Constr #

dataTypeOf :: TargetGrant -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TargetGrant) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TargetGrant) #

gmapT :: (forall b. Data b => b -> b) -> TargetGrant -> TargetGrant #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TargetGrant -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TargetGrant -> r #

gmapQ :: (forall d. Data d => d -> u) -> TargetGrant -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TargetGrant -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TargetGrant -> m TargetGrant #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TargetGrant -> m TargetGrant #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TargetGrant -> m TargetGrant #

Read TargetGrant Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Show TargetGrant Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Generic TargetGrant Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Associated Types

type Rep TargetGrant :: Type -> Type #

Hashable TargetGrant Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

FromXML TargetGrant Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

ToXML TargetGrant Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

toXML :: TargetGrant -> XML #

NFData TargetGrant Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

rnf :: TargetGrant -> () #

type Rep TargetGrant Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

type Rep TargetGrant = D1 (MetaData "TargetGrant" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" False) (C1 (MetaCons "TargetGrant'" PrefixI True) (S1 (MetaSel (Just "_tgPermission") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe BucketLogsPermission)) :*: S1 (MetaSel (Just "_tgGrantee") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Grantee))))

targetGrant :: TargetGrant Source #

Creates a value of TargetGrant with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • tgPermission - Logging permissions assigned to the Grantee for the bucket.
  • tgGrantee - Undocumented member.

tgPermission :: Lens' TargetGrant (Maybe BucketLogsPermission) Source #

Logging permissions assigned to the Grantee for the bucket.

tgGrantee :: Lens' TargetGrant (Maybe Grantee) Source #

Undocumented member.

TopicConfiguration

data TopicConfiguration Source #

Container for specifying the configuration when you want Amazon S3 to publish events to an Amazon Simple Notification Service (Amazon SNS) topic.

See: topicConfiguration smart constructor.

Instances
Eq TopicConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Data TopicConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TopicConfiguration -> c TopicConfiguration #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TopicConfiguration #

toConstr :: TopicConfiguration -> Constr #

dataTypeOf :: TopicConfiguration -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TopicConfiguration) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TopicConfiguration) #

gmapT :: (forall b. Data b => b -> b) -> TopicConfiguration -> TopicConfiguration #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TopicConfiguration -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TopicConfiguration -> r #

gmapQ :: (forall d. Data d => d -> u) -> TopicConfiguration -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TopicConfiguration -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TopicConfiguration -> m TopicConfiguration #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TopicConfiguration -> m TopicConfiguration #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TopicConfiguration -> m TopicConfiguration #

Read TopicConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Show TopicConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Generic TopicConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Associated Types

type Rep TopicConfiguration :: Type -> Type #

Hashable TopicConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

FromXML TopicConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

ToXML TopicConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

NFData TopicConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

rnf :: TopicConfiguration -> () #

type Rep TopicConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

type Rep TopicConfiguration = D1 (MetaData "TopicConfiguration" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" False) (C1 (MetaCons "TopicConfiguration'" PrefixI True) ((S1 (MetaSel (Just "_tcId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_tcFilter") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe NotificationConfigurationFilter))) :*: (S1 (MetaSel (Just "_tcTopicARN") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text) :*: S1 (MetaSel (Just "_tcEvents") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [Event]))))

topicConfiguration Source #

Creates a value of TopicConfiguration with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • tcId - Undocumented member.
  • tcFilter - Undocumented member.
  • tcTopicARN - Amazon SNS topic ARN to which Amazon S3 will publish a message when it detects events of specified type.
  • tcEvents - Undocumented member.

tcId :: Lens' TopicConfiguration (Maybe Text) Source #

Undocumented member.

tcTopicARN :: Lens' TopicConfiguration Text Source #

Amazon SNS topic ARN to which Amazon S3 will publish a message when it detects events of specified type.

tcEvents :: Lens' TopicConfiguration [Event] Source #

Undocumented member.

Transition

data Transition Source #

See: transition smart constructor.

Instances
Eq Transition Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Data Transition Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Transition -> c Transition #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Transition #

toConstr :: Transition -> Constr #

dataTypeOf :: Transition -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Transition) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Transition) #

gmapT :: (forall b. Data b => b -> b) -> Transition -> Transition #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Transition -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Transition -> r #

gmapQ :: (forall d. Data d => d -> u) -> Transition -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Transition -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Transition -> m Transition #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Transition -> m Transition #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Transition -> m Transition #

Read Transition Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Show Transition Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Generic Transition Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Associated Types

type Rep Transition :: Type -> Type #

Hashable Transition Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

FromXML Transition Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

ToXML Transition Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

toXML :: Transition -> XML #

NFData Transition Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

rnf :: Transition -> () #

type Rep Transition Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

type Rep Transition = D1 (MetaData "Transition" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" False) (C1 (MetaCons "Transition'" PrefixI True) (S1 (MetaSel (Just "_tDays") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Int)) :*: (S1 (MetaSel (Just "_tDate") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe RFC822)) :*: S1 (MetaSel (Just "_tStorageClass") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe TransitionStorageClass)))))

transition :: Transition Source #

Creates a value of Transition with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • tDays - Indicates the lifetime, in days, of the objects that are subject to the rule. The value must be a non-zero positive integer.
  • tDate - Indicates at what date the object is to be moved or deleted. Should be in GMT ISO 8601 Format.
  • tStorageClass - The class of storage used to store the object.

tDays :: Lens' Transition (Maybe Int) Source #

Indicates the lifetime, in days, of the objects that are subject to the rule. The value must be a non-zero positive integer.

tDate :: Lens' Transition (Maybe UTCTime) Source #

Indicates at what date the object is to be moved or deleted. Should be in GMT ISO 8601 Format.

tStorageClass :: Lens' Transition (Maybe TransitionStorageClass) Source #

The class of storage used to store the object.

VersioningConfiguration

data VersioningConfiguration Source #

See: versioningConfiguration smart constructor.

Instances
Eq VersioningConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Data VersioningConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VersioningConfiguration -> c VersioningConfiguration #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c VersioningConfiguration #

toConstr :: VersioningConfiguration -> Constr #

dataTypeOf :: VersioningConfiguration -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c VersioningConfiguration) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VersioningConfiguration) #

gmapT :: (forall b. Data b => b -> b) -> VersioningConfiguration -> VersioningConfiguration #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VersioningConfiguration -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VersioningConfiguration -> r #

gmapQ :: (forall d. Data d => d -> u) -> VersioningConfiguration -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VersioningConfiguration -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VersioningConfiguration -> m VersioningConfiguration #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VersioningConfiguration -> m VersioningConfiguration #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VersioningConfiguration -> m VersioningConfiguration #

Read VersioningConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Show VersioningConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Generic VersioningConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Associated Types

type Rep VersioningConfiguration :: Type -> Type #

Hashable VersioningConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

ToXML VersioningConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

NFData VersioningConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

rnf :: VersioningConfiguration -> () #

type Rep VersioningConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

type Rep VersioningConfiguration = D1 (MetaData "VersioningConfiguration" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" False) (C1 (MetaCons "VersioningConfiguration'" PrefixI True) (S1 (MetaSel (Just "_vcStatus") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe BucketVersioningStatus)) :*: S1 (MetaSel (Just "_vcMFADelete") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe MFADelete))))

versioningConfiguration :: VersioningConfiguration Source #

Creates a value of VersioningConfiguration with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • vcStatus - The versioning state of the bucket.
  • vcMFADelete - Specifies whether MFA delete is enabled in the bucket versioning configuration. This element is only returned if the bucket has been configured with MFA delete. If the bucket has never been so configured, this element is not returned.

vcMFADelete :: Lens' VersioningConfiguration (Maybe MFADelete) Source #

Specifies whether MFA delete is enabled in the bucket versioning configuration. This element is only returned if the bucket has been configured with MFA delete. If the bucket has never been so configured, this element is not returned.

WebsiteConfiguration

data WebsiteConfiguration Source #

See: websiteConfiguration smart constructor.

Instances
Eq WebsiteConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Data WebsiteConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> WebsiteConfiguration -> c WebsiteConfiguration #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c WebsiteConfiguration #

toConstr :: WebsiteConfiguration -> Constr #

dataTypeOf :: WebsiteConfiguration -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c WebsiteConfiguration) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c WebsiteConfiguration) #

gmapT :: (forall b. Data b => b -> b) -> WebsiteConfiguration -> WebsiteConfiguration #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> WebsiteConfiguration -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> WebsiteConfiguration -> r #

gmapQ :: (forall d. Data d => d -> u) -> WebsiteConfiguration -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> WebsiteConfiguration -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> WebsiteConfiguration -> m WebsiteConfiguration #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> WebsiteConfiguration -> m WebsiteConfiguration #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> WebsiteConfiguration -> m WebsiteConfiguration #

Read WebsiteConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Show WebsiteConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Generic WebsiteConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Associated Types

type Rep WebsiteConfiguration :: Type -> Type #

Hashable WebsiteConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

ToXML WebsiteConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

NFData WebsiteConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

Methods

rnf :: WebsiteConfiguration -> () #

type Rep WebsiteConfiguration Source # 
Instance details

Defined in Network.AWS.S3.Types.Product

type Rep WebsiteConfiguration = D1 (MetaData "WebsiteConfiguration" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.1-I7VsiKive605KPmKsVgrUz" False) (C1 (MetaCons "WebsiteConfiguration'" PrefixI True) ((S1 (MetaSel (Just "_wcRedirectAllRequestsTo") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe RedirectAllRequestsTo)) :*: S1 (MetaSel (Just "_wcErrorDocument") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ErrorDocument))) :*: (S1 (MetaSel (Just "_wcIndexDocument") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe IndexDocument)) :*: S1 (MetaSel (Just "_wcRoutingRules") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [RoutingRule])))))

websiteConfiguration :: WebsiteConfiguration Source #

Creates a value of WebsiteConfiguration with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired: