amazonka-s3-1.6.0: 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.Types

Contents

Description

 

Synopsis

Service Configuration

s3 :: Service Source #

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

Errors

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

Prism for BucketAlreadyOwnedByYou' errors.

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

This operation is not allowed against this storage tier

_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 :: 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 :: AsError a => Getting (First ServiceError) a ServiceError Source #

The specified multipart upload does not exist.

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

The specified bucket does not exist.

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

The specified key does not exist.

Re-exported Types

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 
Enum Region 
Eq Region 

Methods

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

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

Data Region 

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 
Read Region 
Show Region 
Generic Region 

Associated Types

type Rep Region :: * -> * #

Methods

from :: Region -> Rep Region x #

to :: Rep Region x -> Region #

Hashable Region 

Methods

hashWithSalt :: Int -> Region -> Int #

hash :: Region -> Int #

ToJSON Region 
FromJSON Region 
NFData Region 

Methods

rnf :: Region -> () #

FromXML Region 
ToXML Region 

Methods

toXML :: Region -> XML #

ToLog Region 

Methods

build :: Region -> Builder #

ToByteString Region 

Methods

toBS :: Region -> ByteString #

FromText Region 

Methods

parser :: Parser Region #

ToText Region 

Methods

toText :: Region -> Text #

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

newtype BucketName Source #

Constructors

BucketName Text 

Instances

Eq BucketName Source # 
Data BucketName Source # 

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 # 
Read BucketName Source # 
Show BucketName Source # 
IsString BucketName Source # 
Generic BucketName Source # 

Associated Types

type Rep BucketName :: * -> * #

Hashable BucketName Source # 
FromJSON BucketName Source # 
NFData BucketName Source # 

Methods

rnf :: BucketName -> () #

FromXML BucketName Source # 
ToXML BucketName Source # 

Methods

toXML :: BucketName -> XML #

ToLog BucketName Source # 

Methods

build :: BucketName -> Builder #

ToQuery BucketName Source # 
ToByteString BucketName Source # 
FromText BucketName Source # 
ToText BucketName Source # 

Methods

toText :: BucketName -> Text #

type Rep BucketName Source # 
type Rep BucketName = D1 * (MetaData "BucketName" "Network.AWS.S3.Internal" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" True) (C1 * (MetaCons "BucketName" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)))

newtype ETag Source #

Constructors

ETag ByteString 

Instances

Eq ETag Source # 

Methods

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

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

Data ETag Source # 

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 # 

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 # 
Show ETag Source # 

Methods

showsPrec :: Int -> ETag -> ShowS #

show :: ETag -> String #

showList :: [ETag] -> ShowS #

IsString ETag Source # 

Methods

fromString :: String -> ETag #

Generic ETag Source # 

Associated Types

type Rep ETag :: * -> * #

Methods

from :: ETag -> Rep ETag x #

to :: Rep ETag x -> ETag #

Hashable ETag Source # 

Methods

hashWithSalt :: Int -> ETag -> Int #

hash :: ETag -> Int #

NFData ETag Source # 

Methods

rnf :: ETag -> () #

FromXML ETag Source # 

Methods

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

ToXML ETag Source # 

Methods

toXML :: ETag -> XML #

ToLog ETag Source # 

Methods

build :: ETag -> Builder #

ToQuery ETag Source # 

Methods

toQuery :: ETag -> QueryString #

ToByteString ETag Source # 

Methods

toBS :: ETag -> ByteString #

FromText ETag Source # 

Methods

parser :: Parser ETag #

ToText ETag Source # 

Methods

toText :: ETag -> Text #

type Rep ETag Source # 
type Rep ETag = D1 * (MetaData "ETag" "Network.AWS.S3.Internal" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" True) (C1 * (MetaCons "ETag" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * ByteString)))

newtype ObjectVersionId Source #

Constructors

ObjectVersionId Text 

Instances

Eq ObjectVersionId Source # 
Data ObjectVersionId Source # 

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 # 
Read ObjectVersionId Source # 
Show ObjectVersionId Source # 
IsString ObjectVersionId Source # 
Generic ObjectVersionId Source # 
Hashable ObjectVersionId Source # 
NFData ObjectVersionId Source # 

Methods

rnf :: ObjectVersionId -> () #

FromXML ObjectVersionId Source # 
ToXML ObjectVersionId Source # 

Methods

toXML :: ObjectVersionId -> XML #

ToLog ObjectVersionId Source # 
ToQuery ObjectVersionId Source # 
ToByteString ObjectVersionId Source # 
FromText ObjectVersionId Source # 
ToText ObjectVersionId Source # 
type Rep ObjectVersionId Source # 
type Rep ObjectVersionId = D1 * (MetaData "ObjectVersionId" "Network.AWS.S3.Internal" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" True) (C1 * (MetaCons "ObjectVersionId" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)))

Bucket Location

newtype LocationConstraint Source #

Instances

Eq LocationConstraint Source # 
Data LocationConstraint Source # 

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 # 
Read LocationConstraint Source # 
Show LocationConstraint Source # 
Generic LocationConstraint Source # 
Hashable LocationConstraint Source # 
NFData LocationConstraint Source # 

Methods

rnf :: LocationConstraint -> () #

FromXML LocationConstraint Source # 
ToXML LocationConstraint Source # 
ToLog LocationConstraint Source # 
ToByteString LocationConstraint Source # 
FromText LocationConstraint Source # 
ToText LocationConstraint Source # 
type Rep LocationConstraint Source # 
type Rep LocationConstraint = D1 * (MetaData "LocationConstraint" "Network.AWS.S3.Internal" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" True) (C1 * (MetaCons "LocationConstraint" PrefixI True) (S1 * (MetaSel (Just Symbol "constraintRegion") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Region)))

Object Key

newtype ObjectKey Source #

Constructors

ObjectKey Text 

Instances

Eq ObjectKey Source # 
Data ObjectKey Source # 

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 # 
Read ObjectKey Source # 
Show ObjectKey Source # 
IsString ObjectKey Source # 
Generic ObjectKey Source # 

Associated Types

type Rep ObjectKey :: * -> * #

Hashable ObjectKey Source # 
NFData ObjectKey Source # 

Methods

rnf :: ObjectKey -> () #

FromXML ObjectKey Source # 
ToXML ObjectKey Source # 

Methods

toXML :: ObjectKey -> XML #

ToLog ObjectKey Source # 

Methods

build :: ObjectKey -> Builder #

ToPath ObjectKey Source # 
ToQuery ObjectKey Source # 
ToByteString ObjectKey Source # 

Methods

toBS :: ObjectKey -> ByteString #

FromText ObjectKey Source # 
ToText ObjectKey Source # 

Methods

toText :: ObjectKey -> Text #

type Rep ObjectKey Source # 
type Rep ObjectKey = D1 * (MetaData "ObjectKey" "Network.AWS.S3.Internal" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" True) (C1 * (MetaCons "ObjectKey" PrefixI False) (S1 * (MetaSel (Nothing 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 # 
Enum AnalyticsS3ExportFileFormat Source # 
Eq AnalyticsS3ExportFileFormat Source # 
Data AnalyticsS3ExportFileFormat Source # 

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 # 
Read AnalyticsS3ExportFileFormat Source # 
Show AnalyticsS3ExportFileFormat Source # 
Generic AnalyticsS3ExportFileFormat Source # 
Hashable AnalyticsS3ExportFileFormat Source # 
NFData AnalyticsS3ExportFileFormat Source # 
FromXML AnalyticsS3ExportFileFormat Source # 
ToXML AnalyticsS3ExportFileFormat Source # 
ToHeader AnalyticsS3ExportFileFormat Source # 
ToQuery AnalyticsS3ExportFileFormat Source # 
ToByteString AnalyticsS3ExportFileFormat Source # 
FromText AnalyticsS3ExportFileFormat Source # 
ToText AnalyticsS3ExportFileFormat Source # 
type Rep AnalyticsS3ExportFileFormat Source # 
type Rep AnalyticsS3ExportFileFormat = D1 * (MetaData "AnalyticsS3ExportFileFormat" "Network.AWS.S3.Types.Sum" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" False) (C1 * (MetaCons "CSV" PrefixI False) (U1 *))

BucketAccelerateStatus

data BucketAccelerateStatus Source #

Constructors

BASEnabled 
BASSuspended 

Instances

Bounded BucketAccelerateStatus Source # 
Enum BucketAccelerateStatus Source # 
Eq BucketAccelerateStatus Source # 
Data BucketAccelerateStatus Source # 

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 # 
Read BucketAccelerateStatus Source # 
Show BucketAccelerateStatus Source # 
Generic BucketAccelerateStatus Source # 
Hashable BucketAccelerateStatus Source # 
NFData BucketAccelerateStatus Source # 

Methods

rnf :: BucketAccelerateStatus -> () #

FromXML BucketAccelerateStatus Source # 
ToXML BucketAccelerateStatus Source # 
ToHeader BucketAccelerateStatus Source # 
ToQuery BucketAccelerateStatus Source # 
ToByteString BucketAccelerateStatus Source # 
FromText BucketAccelerateStatus Source # 
ToText BucketAccelerateStatus Source # 
type Rep BucketAccelerateStatus Source # 
type Rep BucketAccelerateStatus = D1 * (MetaData "BucketAccelerateStatus" "Network.AWS.S3.Types.Sum" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" False) ((:+:) * (C1 * (MetaCons "BASEnabled" PrefixI False) (U1 *)) (C1 * (MetaCons "BASSuspended" PrefixI False) (U1 *)))

BucketCannedACL

data BucketCannedACL Source #

Instances

Bounded BucketCannedACL Source # 
Enum BucketCannedACL Source # 
Eq BucketCannedACL Source # 
Data BucketCannedACL Source # 

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 # 
Read BucketCannedACL Source # 
Show BucketCannedACL Source # 
Generic BucketCannedACL Source # 
Hashable BucketCannedACL Source # 
NFData BucketCannedACL Source # 

Methods

rnf :: BucketCannedACL -> () #

ToXML BucketCannedACL Source # 

Methods

toXML :: BucketCannedACL -> XML #

ToHeader BucketCannedACL Source # 
ToQuery BucketCannedACL Source # 
ToByteString BucketCannedACL Source # 
FromText BucketCannedACL Source # 
ToText BucketCannedACL Source # 
type Rep BucketCannedACL Source # 
type Rep BucketCannedACL = D1 * (MetaData "BucketCannedACL" "Network.AWS.S3.Types.Sum" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" False) ((:+:) * ((:+:) * (C1 * (MetaCons "BAuthenticatedRead" PrefixI False) (U1 *)) (C1 * (MetaCons "BPrivate" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "BPublicRead" PrefixI False) (U1 *)) (C1 * (MetaCons "BPublicReadWrite" PrefixI False) (U1 *))))

BucketLogsPermission

data BucketLogsPermission Source #

Constructors

FullControl 
Read 
Write 

Instances

Bounded BucketLogsPermission Source # 
Enum BucketLogsPermission Source # 
Eq BucketLogsPermission Source # 
Data BucketLogsPermission Source # 

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 # 
Read BucketLogsPermission Source # 
Show BucketLogsPermission Source # 
Generic BucketLogsPermission Source # 
Hashable BucketLogsPermission Source # 
NFData BucketLogsPermission Source # 

Methods

rnf :: BucketLogsPermission -> () #

FromXML BucketLogsPermission Source # 
ToXML BucketLogsPermission Source # 
ToHeader BucketLogsPermission Source # 
ToQuery BucketLogsPermission Source # 
ToByteString BucketLogsPermission Source # 
FromText BucketLogsPermission Source # 
ToText BucketLogsPermission Source # 
type Rep BucketLogsPermission Source # 
type Rep BucketLogsPermission = D1 * (MetaData "BucketLogsPermission" "Network.AWS.S3.Types.Sum" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" False) ((:+:) * (C1 * (MetaCons "FullControl" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "Read" PrefixI False) (U1 *)) (C1 * (MetaCons "Write" PrefixI False) (U1 *))))

BucketVersioningStatus

data BucketVersioningStatus Source #

Constructors

BVSEnabled 
BVSSuspended 

Instances

Bounded BucketVersioningStatus Source # 
Enum BucketVersioningStatus Source # 
Eq BucketVersioningStatus Source # 
Data BucketVersioningStatus Source # 

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 # 
Read BucketVersioningStatus Source # 
Show BucketVersioningStatus Source # 
Generic BucketVersioningStatus Source # 
Hashable BucketVersioningStatus Source # 
NFData BucketVersioningStatus Source # 

Methods

rnf :: BucketVersioningStatus -> () #

FromXML BucketVersioningStatus Source # 
ToXML BucketVersioningStatus Source # 
ToHeader BucketVersioningStatus Source # 
ToQuery BucketVersioningStatus Source # 
ToByteString BucketVersioningStatus Source # 
FromText BucketVersioningStatus Source # 
ToText BucketVersioningStatus Source # 
type Rep BucketVersioningStatus Source # 
type Rep BucketVersioningStatus = D1 * (MetaData "BucketVersioningStatus" "Network.AWS.S3.Types.Sum" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" False) ((:+:) * (C1 * (MetaCons "BVSEnabled" PrefixI False) (U1 *)) (C1 * (MetaCons "BVSSuspended" PrefixI False) (U1 *)))

CompressionType

data CompressionType Source #

Constructors

CTGzip 
CTNone 

Instances

Bounded CompressionType Source # 
Enum CompressionType Source # 
Eq CompressionType Source # 
Data CompressionType Source # 

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 # 
Read CompressionType Source # 
Show CompressionType Source # 
Generic CompressionType Source # 
Hashable CompressionType Source # 
NFData CompressionType Source # 

Methods

rnf :: CompressionType -> () #

ToXML CompressionType Source # 

Methods

toXML :: CompressionType -> XML #

ToHeader CompressionType Source # 
ToQuery CompressionType Source # 
ToByteString CompressionType Source # 
FromText CompressionType Source # 
ToText CompressionType Source # 
type Rep CompressionType Source # 
type Rep CompressionType = D1 * (MetaData "CompressionType" "Network.AWS.S3.Types.Sum" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" False) ((:+:) * (C1 * (MetaCons "CTGzip" PrefixI False) (U1 *)) (C1 * (MetaCons "CTNone" PrefixI False) (U1 *)))

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 # 
Enum EncodingType Source # 
Eq EncodingType Source # 
Data EncodingType Source # 

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 # 
Read EncodingType Source # 
Show EncodingType Source # 
Generic EncodingType Source # 

Associated Types

type Rep EncodingType :: * -> * #

Hashable EncodingType Source # 
NFData EncodingType Source # 

Methods

rnf :: EncodingType -> () #

FromXML EncodingType Source # 
ToXML EncodingType Source # 

Methods

toXML :: EncodingType -> XML #

ToHeader EncodingType Source # 
ToQuery EncodingType Source # 
ToByteString EncodingType Source # 
FromText EncodingType Source # 
ToText EncodingType Source # 

Methods

toText :: EncodingType -> Text #

type Rep EncodingType Source # 
type Rep EncodingType = D1 * (MetaData "EncodingType" "Network.AWS.S3.Types.Sum" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" False) (C1 * (MetaCons "URL" PrefixI False) (U1 *))

Event

data Event Source #

Bucket event for which to send notifications.

Instances

Bounded Event Source # 
Enum Event Source # 
Eq Event Source # 

Methods

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

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

Data Event Source # 

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 # 

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 # 
Show Event Source # 

Methods

showsPrec :: Int -> Event -> ShowS #

show :: Event -> String #

showList :: [Event] -> ShowS #

Generic Event Source # 

Associated Types

type Rep Event :: * -> * #

Methods

from :: Event -> Rep Event x #

to :: Rep Event x -> Event #

Hashable Event Source # 

Methods

hashWithSalt :: Int -> Event -> Int #

hash :: Event -> Int #

NFData Event Source # 

Methods

rnf :: Event -> () #

FromXML Event Source # 

Methods

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

ToXML Event Source # 

Methods

toXML :: Event -> XML #

ToHeader Event Source # 

Methods

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

ToQuery Event Source # 

Methods

toQuery :: Event -> QueryString #

ToByteString Event Source # 

Methods

toBS :: Event -> ByteString #

FromText Event Source # 

Methods

parser :: Parser Event #

ToText Event Source # 

Methods

toText :: Event -> Text #

type Rep Event Source # 
type Rep Event = D1 * (MetaData "Event" "Network.AWS.S3.Types.Sum" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" False) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "S3ObjectCreated" PrefixI False) (U1 *)) (C1 * (MetaCons "S3ObjectCreatedCompleteMultipartUpload" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "S3ObjectCreatedCopy" PrefixI False) (U1 *)) (C1 * (MetaCons "S3ObjectCreatedPost" PrefixI False) (U1 *)))) ((:+:) * ((:+:) * (C1 * (MetaCons "S3ObjectCreatedPut" PrefixI False) (U1 *)) (C1 * (MetaCons "S3ObjectRemoved" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "S3ObjectRemovedDelete" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "S3ObjectRemovedDeleteMarkerCreated" PrefixI False) (U1 *)) (C1 * (MetaCons "S3ReducedRedundancyLostObject" PrefixI False) (U1 *))))))

ExpirationStatus

data ExpirationStatus Source #

Constructors

ESDisabled 
ESEnabled 

Instances

Bounded ExpirationStatus Source # 
Enum ExpirationStatus Source # 
Eq ExpirationStatus Source # 
Data ExpirationStatus Source # 

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 # 
Read ExpirationStatus Source # 
Show ExpirationStatus Source # 
Generic ExpirationStatus Source # 
Hashable ExpirationStatus Source # 
NFData ExpirationStatus Source # 

Methods

rnf :: ExpirationStatus -> () #

FromXML ExpirationStatus Source # 
ToXML ExpirationStatus Source # 
ToHeader ExpirationStatus Source # 
ToQuery ExpirationStatus Source # 
ToByteString ExpirationStatus Source # 
FromText ExpirationStatus Source # 
ToText ExpirationStatus Source # 
type Rep ExpirationStatus Source # 
type Rep ExpirationStatus = D1 * (MetaData "ExpirationStatus" "Network.AWS.S3.Types.Sum" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" False) ((:+:) * (C1 * (MetaCons "ESDisabled" PrefixI False) (U1 *)) (C1 * (MetaCons "ESEnabled" PrefixI False) (U1 *)))

ExpressionType

data ExpressionType Source #

Constructors

Sql 

Instances

Bounded ExpressionType Source # 
Enum ExpressionType Source # 
Eq ExpressionType Source # 
Data ExpressionType Source # 

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 # 
Read ExpressionType Source # 
Show ExpressionType Source # 
Generic ExpressionType Source # 

Associated Types

type Rep ExpressionType :: * -> * #

Hashable ExpressionType Source # 
NFData ExpressionType Source # 

Methods

rnf :: ExpressionType -> () #

ToXML ExpressionType Source # 

Methods

toXML :: ExpressionType -> XML #

ToHeader ExpressionType Source # 
ToQuery ExpressionType Source # 
ToByteString ExpressionType Source # 
FromText ExpressionType Source # 
ToText ExpressionType Source # 
type Rep ExpressionType Source # 
type Rep ExpressionType = D1 * (MetaData "ExpressionType" "Network.AWS.S3.Types.Sum" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" False) (C1 * (MetaCons "Sql" PrefixI False) (U1 *))

FileHeaderInfo

data FileHeaderInfo Source #

Constructors

Ignore 
None 
Use 

Instances

Bounded FileHeaderInfo Source # 
Enum FileHeaderInfo Source # 
Eq FileHeaderInfo Source # 
Data FileHeaderInfo Source # 

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 # 
Read FileHeaderInfo Source # 
Show FileHeaderInfo Source # 
Generic FileHeaderInfo Source # 

Associated Types

type Rep FileHeaderInfo :: * -> * #

Hashable FileHeaderInfo Source # 
NFData FileHeaderInfo Source # 

Methods

rnf :: FileHeaderInfo -> () #

ToXML FileHeaderInfo Source # 

Methods

toXML :: FileHeaderInfo -> XML #

ToHeader FileHeaderInfo Source # 
ToQuery FileHeaderInfo Source # 
ToByteString FileHeaderInfo Source # 
FromText FileHeaderInfo Source # 
ToText FileHeaderInfo Source # 
type Rep FileHeaderInfo Source # 
type Rep FileHeaderInfo = D1 * (MetaData "FileHeaderInfo" "Network.AWS.S3.Types.Sum" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" False) ((:+:) * (C1 * (MetaCons "Ignore" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "None" PrefixI False) (U1 *)) (C1 * (MetaCons "Use" PrefixI False) (U1 *))))

FilterRuleName

data FilterRuleName Source #

Constructors

Prefix 
Suffix 

Instances

Bounded FilterRuleName Source # 
Enum FilterRuleName Source # 
Eq FilterRuleName Source # 
Data FilterRuleName Source # 

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 # 
Read FilterRuleName Source # 
Show FilterRuleName Source # 
Generic FilterRuleName Source # 

Associated Types

type Rep FilterRuleName :: * -> * #

Hashable FilterRuleName Source # 
NFData FilterRuleName Source # 

Methods

rnf :: FilterRuleName -> () #

FromXML FilterRuleName Source # 
ToXML FilterRuleName Source # 

Methods

toXML :: FilterRuleName -> XML #

ToHeader FilterRuleName Source # 
ToQuery FilterRuleName Source # 
ToByteString FilterRuleName Source # 
FromText FilterRuleName Source # 
ToText FilterRuleName Source # 
type Rep FilterRuleName Source # 
type Rep FilterRuleName = D1 * (MetaData "FilterRuleName" "Network.AWS.S3.Types.Sum" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" False) ((:+:) * (C1 * (MetaCons "Prefix" PrefixI False) (U1 *)) (C1 * (MetaCons "Suffix" PrefixI False) (U1 *)))

InventoryFormat

data InventoryFormat Source #

Constructors

IFCSV 
IFOrc 

Instances

Bounded InventoryFormat Source # 
Enum InventoryFormat Source # 
Eq InventoryFormat Source # 
Data InventoryFormat Source # 

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 # 
Read InventoryFormat Source # 
Show InventoryFormat Source # 
Generic InventoryFormat Source # 
Hashable InventoryFormat Source # 
NFData InventoryFormat Source # 

Methods

rnf :: InventoryFormat -> () #

FromXML InventoryFormat Source # 
ToXML InventoryFormat Source # 

Methods

toXML :: InventoryFormat -> XML #

ToHeader InventoryFormat Source # 
ToQuery InventoryFormat Source # 
ToByteString InventoryFormat Source # 
FromText InventoryFormat Source # 
ToText InventoryFormat Source # 
type Rep InventoryFormat Source # 
type Rep InventoryFormat = D1 * (MetaData "InventoryFormat" "Network.AWS.S3.Types.Sum" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" False) ((:+:) * (C1 * (MetaCons "IFCSV" PrefixI False) (U1 *)) (C1 * (MetaCons "IFOrc" PrefixI False) (U1 *)))

InventoryFrequency

data InventoryFrequency Source #

Constructors

Daily 
Weekly 

Instances

Bounded InventoryFrequency Source # 
Enum InventoryFrequency Source # 
Eq InventoryFrequency Source # 
Data InventoryFrequency Source # 

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 # 
Read InventoryFrequency Source # 
Show InventoryFrequency Source # 
Generic InventoryFrequency Source # 
Hashable InventoryFrequency Source # 
NFData InventoryFrequency Source # 

Methods

rnf :: InventoryFrequency -> () #

FromXML InventoryFrequency Source # 
ToXML InventoryFrequency Source # 
ToHeader InventoryFrequency Source # 
ToQuery InventoryFrequency Source # 
ToByteString InventoryFrequency Source # 
FromText InventoryFrequency Source # 
ToText InventoryFrequency Source # 
type Rep InventoryFrequency Source # 
type Rep InventoryFrequency = D1 * (MetaData "InventoryFrequency" "Network.AWS.S3.Types.Sum" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" False) ((:+:) * (C1 * (MetaCons "Daily" PrefixI False) (U1 *)) (C1 * (MetaCons "Weekly" PrefixI False) (U1 *)))

InventoryIncludedObjectVersions

data InventoryIncludedObjectVersions Source #

Constructors

All 
Current 

Instances

Bounded InventoryIncludedObjectVersions Source # 
Enum InventoryIncludedObjectVersions Source # 
Eq InventoryIncludedObjectVersions Source # 
Data InventoryIncludedObjectVersions Source # 

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 # 
Read InventoryIncludedObjectVersions Source # 
Show InventoryIncludedObjectVersions Source # 
Generic InventoryIncludedObjectVersions Source # 
Hashable InventoryIncludedObjectVersions Source # 
NFData InventoryIncludedObjectVersions Source # 
FromXML InventoryIncludedObjectVersions Source # 
ToXML InventoryIncludedObjectVersions Source # 
ToHeader InventoryIncludedObjectVersions Source # 
ToQuery InventoryIncludedObjectVersions Source # 
ToByteString InventoryIncludedObjectVersions Source # 
FromText InventoryIncludedObjectVersions Source # 
ToText InventoryIncludedObjectVersions Source # 
type Rep InventoryIncludedObjectVersions Source # 
type Rep InventoryIncludedObjectVersions = D1 * (MetaData "InventoryIncludedObjectVersions" "Network.AWS.S3.Types.Sum" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" False) ((:+:) * (C1 * (MetaCons "All" PrefixI False) (U1 *)) (C1 * (MetaCons "Current" PrefixI False) (U1 *)))

InventoryOptionalField

data InventoryOptionalField Source #

Instances

Bounded InventoryOptionalField Source # 
Enum InventoryOptionalField Source # 
Eq InventoryOptionalField Source # 
Data InventoryOptionalField Source # 

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 # 
Read InventoryOptionalField Source # 
Show InventoryOptionalField Source # 
Generic InventoryOptionalField Source # 
Hashable InventoryOptionalField Source # 
NFData InventoryOptionalField Source # 

Methods

rnf :: InventoryOptionalField -> () #

FromXML InventoryOptionalField Source # 
ToXML InventoryOptionalField Source # 
ToHeader InventoryOptionalField Source # 
ToQuery InventoryOptionalField Source # 
ToByteString InventoryOptionalField Source # 
FromText InventoryOptionalField Source # 
ToText InventoryOptionalField Source # 
type Rep InventoryOptionalField Source # 
type Rep InventoryOptionalField = D1 * (MetaData "InventoryOptionalField" "Network.AWS.S3.Types.Sum" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" False) ((:+:) * ((:+:) * (C1 * (MetaCons "FieldETag" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "FieldEncryptionStatus" PrefixI False) (U1 *)) (C1 * (MetaCons "FieldIsMultipartUploaded" PrefixI False) (U1 *)))) ((:+:) * ((:+:) * (C1 * (MetaCons "FieldLastModifiedDate" PrefixI False) (U1 *)) (C1 * (MetaCons "FieldReplicationStatus" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "FieldSize" PrefixI False) (U1 *)) (C1 * (MetaCons "FieldStorageClass" PrefixI False) (U1 *)))))

JSONType

data JSONType Source #

Constructors

Document 
Lines 

Instances

Bounded JSONType Source # 
Enum JSONType Source # 
Eq JSONType Source # 
Data JSONType Source # 

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 # 
Read JSONType Source # 
Show JSONType Source # 
Generic JSONType Source # 

Associated Types

type Rep JSONType :: * -> * #

Methods

from :: JSONType -> Rep JSONType x #

to :: Rep JSONType x -> JSONType #

Hashable JSONType Source # 

Methods

hashWithSalt :: Int -> JSONType -> Int #

hash :: JSONType -> Int #

NFData JSONType Source # 

Methods

rnf :: JSONType -> () #

ToXML JSONType Source # 

Methods

toXML :: JSONType -> XML #

ToHeader JSONType Source # 

Methods

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

ToQuery JSONType Source # 
ToByteString JSONType Source # 

Methods

toBS :: JSONType -> ByteString #

FromText JSONType Source # 
ToText JSONType Source # 

Methods

toText :: JSONType -> Text #

type Rep JSONType Source # 
type Rep JSONType = D1 * (MetaData "JSONType" "Network.AWS.S3.Types.Sum" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" False) ((:+:) * (C1 * (MetaCons "Document" PrefixI False) (U1 *)) (C1 * (MetaCons "Lines" PrefixI False) (U1 *)))

MFADelete

data MFADelete Source #

Constructors

MDDisabled 
MDEnabled 

Instances

Bounded MFADelete Source # 
Enum MFADelete Source # 
Eq MFADelete Source # 
Data MFADelete Source # 

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 # 
Read MFADelete Source # 
Show MFADelete Source # 
Generic MFADelete Source # 

Associated Types

type Rep MFADelete :: * -> * #

Hashable MFADelete Source # 
NFData MFADelete Source # 

Methods

rnf :: MFADelete -> () #

ToXML MFADelete Source # 

Methods

toXML :: MFADelete -> XML #

ToHeader MFADelete Source # 
ToQuery MFADelete Source # 
ToByteString MFADelete Source # 

Methods

toBS :: MFADelete -> ByteString #

FromText MFADelete Source # 
ToText MFADelete Source # 

Methods

toText :: MFADelete -> Text #

type Rep MFADelete Source # 
type Rep MFADelete = D1 * (MetaData "MFADelete" "Network.AWS.S3.Types.Sum" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" False) ((:+:) * (C1 * (MetaCons "MDDisabled" PrefixI False) (U1 *)) (C1 * (MetaCons "MDEnabled" PrefixI False) (U1 *)))

MFADeleteStatus

data MFADeleteStatus Source #

Constructors

MDSDisabled 
MDSEnabled 

Instances

Bounded MFADeleteStatus Source # 
Enum MFADeleteStatus Source # 
Eq MFADeleteStatus Source # 
Data MFADeleteStatus Source # 

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 # 
Read MFADeleteStatus Source # 
Show MFADeleteStatus Source # 
Generic MFADeleteStatus Source # 
Hashable MFADeleteStatus Source # 
NFData MFADeleteStatus Source # 

Methods

rnf :: MFADeleteStatus -> () #

FromXML MFADeleteStatus Source # 
ToHeader MFADeleteStatus Source # 
ToQuery MFADeleteStatus Source # 
ToByteString MFADeleteStatus Source # 
FromText MFADeleteStatus Source # 
ToText MFADeleteStatus Source # 
type Rep MFADeleteStatus Source # 
type Rep MFADeleteStatus = D1 * (MetaData "MFADeleteStatus" "Network.AWS.S3.Types.Sum" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" False) ((:+:) * (C1 * (MetaCons "MDSDisabled" PrefixI False) (U1 *)) (C1 * (MetaCons "MDSEnabled" PrefixI False) (U1 *)))

MetadataDirective

data MetadataDirective Source #

Constructors

MDCopy 
MDReplace 

Instances

Bounded MetadataDirective Source # 
Enum MetadataDirective Source # 
Eq MetadataDirective Source # 
Data MetadataDirective Source # 

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 # 
Read MetadataDirective Source # 
Show MetadataDirective Source # 
Generic MetadataDirective Source # 
Hashable MetadataDirective Source # 
NFData MetadataDirective Source # 

Methods

rnf :: MetadataDirective -> () #

ToXML MetadataDirective Source # 
ToHeader MetadataDirective Source # 
ToQuery MetadataDirective Source # 
ToByteString MetadataDirective Source # 
FromText MetadataDirective Source # 
ToText MetadataDirective Source # 
type Rep MetadataDirective Source # 
type Rep MetadataDirective = D1 * (MetaData "MetadataDirective" "Network.AWS.S3.Types.Sum" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" False) ((:+:) * (C1 * (MetaCons "MDCopy" PrefixI False) (U1 *)) (C1 * (MetaCons "MDReplace" PrefixI False) (U1 *)))

ObjectCannedACL

data ObjectCannedACL Source #

Instances

Bounded ObjectCannedACL Source # 
Enum ObjectCannedACL Source # 
Eq ObjectCannedACL Source # 
Data ObjectCannedACL Source # 

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 # 
Read ObjectCannedACL Source # 
Show ObjectCannedACL Source # 
Generic ObjectCannedACL Source # 
Hashable ObjectCannedACL Source # 
NFData ObjectCannedACL Source # 

Methods

rnf :: ObjectCannedACL -> () #

ToXML ObjectCannedACL Source # 

Methods

toXML :: ObjectCannedACL -> XML #

ToHeader ObjectCannedACL Source # 
ToQuery ObjectCannedACL Source # 
ToByteString ObjectCannedACL Source # 
FromText ObjectCannedACL Source # 
ToText ObjectCannedACL Source # 
type Rep ObjectCannedACL Source # 
type Rep ObjectCannedACL = D1 * (MetaData "ObjectCannedACL" "Network.AWS.S3.Types.Sum" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" False) ((:+:) * ((:+:) * (C1 * (MetaCons "OAWSExecRead" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "OAuthenticatedRead" PrefixI False) (U1 *)) (C1 * (MetaCons "OBucketOwnerFullControl" PrefixI False) (U1 *)))) ((:+:) * ((:+:) * (C1 * (MetaCons "OBucketOwnerRead" PrefixI False) (U1 *)) (C1 * (MetaCons "OPrivate" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "OPublicRead" PrefixI False) (U1 *)) (C1 * (MetaCons "OPublicReadWrite" PrefixI False) (U1 *)))))

ObjectStorageClass

data ObjectStorageClass Source #

Instances

Bounded ObjectStorageClass Source # 
Enum ObjectStorageClass Source # 
Eq ObjectStorageClass Source # 
Data ObjectStorageClass Source # 

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 # 
Read ObjectStorageClass Source # 
Show ObjectStorageClass Source # 
Generic ObjectStorageClass Source # 
Hashable ObjectStorageClass Source # 
NFData ObjectStorageClass Source # 

Methods

rnf :: ObjectStorageClass -> () #

FromXML ObjectStorageClass Source # 
ToHeader ObjectStorageClass Source # 
ToQuery ObjectStorageClass Source # 
ToByteString ObjectStorageClass Source # 
FromText ObjectStorageClass Source # 
ToText ObjectStorageClass Source # 
type Rep ObjectStorageClass Source # 
type Rep ObjectStorageClass = D1 * (MetaData "ObjectStorageClass" "Network.AWS.S3.Types.Sum" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" False) ((:+:) * ((:+:) * (C1 * (MetaCons "OSCGlacier" PrefixI False) (U1 *)) (C1 * (MetaCons "OSCReducedRedundancy" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "OSCStandard" PrefixI False) (U1 *)) (C1 * (MetaCons "OSCStandardIA" PrefixI False) (U1 *))))

ObjectVersionStorageClass

data ObjectVersionStorageClass Source #

Constructors

OVSCStandard 

Instances

Bounded ObjectVersionStorageClass Source # 
Enum ObjectVersionStorageClass Source # 
Eq ObjectVersionStorageClass Source # 
Data ObjectVersionStorageClass Source # 

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 # 
Read ObjectVersionStorageClass Source # 
Show ObjectVersionStorageClass Source # 
Generic ObjectVersionStorageClass Source # 
Hashable ObjectVersionStorageClass Source # 
NFData ObjectVersionStorageClass Source # 
FromXML ObjectVersionStorageClass Source # 
ToHeader ObjectVersionStorageClass Source # 
ToQuery ObjectVersionStorageClass Source # 
ToByteString ObjectVersionStorageClass Source # 
FromText ObjectVersionStorageClass Source # 
ToText ObjectVersionStorageClass Source # 
type Rep ObjectVersionStorageClass Source # 
type Rep ObjectVersionStorageClass = D1 * (MetaData "ObjectVersionStorageClass" "Network.AWS.S3.Types.Sum" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" False) (C1 * (MetaCons "OVSCStandard" PrefixI False) (U1 *))

OwnerOverride

data OwnerOverride Source #

Constructors

Destination 

Instances

Bounded OwnerOverride Source # 
Enum OwnerOverride Source # 
Eq OwnerOverride Source # 
Data OwnerOverride Source # 

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 # 
Read OwnerOverride Source # 
Show OwnerOverride Source # 
Generic OwnerOverride Source # 

Associated Types

type Rep OwnerOverride :: * -> * #

Hashable OwnerOverride Source # 
NFData OwnerOverride Source # 

Methods

rnf :: OwnerOverride -> () #

FromXML OwnerOverride Source # 
ToXML OwnerOverride Source # 

Methods

toXML :: OwnerOverride -> XML #

ToHeader OwnerOverride Source # 
ToQuery OwnerOverride Source # 
ToByteString OwnerOverride Source # 
FromText OwnerOverride Source # 
ToText OwnerOverride Source # 

Methods

toText :: OwnerOverride -> Text #

type Rep OwnerOverride Source # 
type Rep OwnerOverride = D1 * (MetaData "OwnerOverride" "Network.AWS.S3.Types.Sum" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" False) (C1 * (MetaCons "Destination" PrefixI False) (U1 *))

Payer

data Payer Source #

Constructors

BucketOwner 
Requester 

Instances

Bounded Payer Source # 
Enum Payer Source # 
Eq Payer Source # 

Methods

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

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

Data Payer Source # 

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 # 

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 # 
Show Payer Source # 

Methods

showsPrec :: Int -> Payer -> ShowS #

show :: Payer -> String #

showList :: [Payer] -> ShowS #

Generic Payer Source # 

Associated Types

type Rep Payer :: * -> * #

Methods

from :: Payer -> Rep Payer x #

to :: Rep Payer x -> Payer #

Hashable Payer Source # 

Methods

hashWithSalt :: Int -> Payer -> Int #

hash :: Payer -> Int #

NFData Payer Source # 

Methods

rnf :: Payer -> () #

FromXML Payer Source # 

Methods

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

ToXML Payer Source # 

Methods

toXML :: Payer -> XML #

ToHeader Payer Source # 

Methods

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

ToQuery Payer Source # 

Methods

toQuery :: Payer -> QueryString #

ToByteString Payer Source # 

Methods

toBS :: Payer -> ByteString #

FromText Payer Source # 

Methods

parser :: Parser Payer #

ToText Payer Source # 

Methods

toText :: Payer -> Text #

type Rep Payer Source # 
type Rep Payer = D1 * (MetaData "Payer" "Network.AWS.S3.Types.Sum" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" False) ((:+:) * (C1 * (MetaCons "BucketOwner" PrefixI False) (U1 *)) (C1 * (MetaCons "Requester" PrefixI False) (U1 *)))

Permission

data Permission Source #

Instances

Bounded Permission Source # 
Enum Permission Source # 
Eq Permission Source # 
Data Permission Source # 

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 # 
Read Permission Source # 
Show Permission Source # 
Generic Permission Source # 

Associated Types

type Rep Permission :: * -> * #

Hashable Permission Source # 
NFData Permission Source # 

Methods

rnf :: Permission -> () #

FromXML Permission Source # 
ToXML Permission Source # 

Methods

toXML :: Permission -> XML #

ToHeader Permission Source # 
ToQuery Permission Source # 
ToByteString Permission Source # 
FromText Permission Source # 
ToText Permission Source # 

Methods

toText :: Permission -> Text #

type Rep Permission Source # 
type Rep Permission = D1 * (MetaData "Permission" "Network.AWS.S3.Types.Sum" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" False) ((:+:) * ((:+:) * (C1 * (MetaCons "PFullControl" PrefixI False) (U1 *)) (C1 * (MetaCons "PRead" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "PReadAcp" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "PWrite" PrefixI False) (U1 *)) (C1 * (MetaCons "PWriteAcp" PrefixI False) (U1 *)))))

Protocol

data Protocol Source #

Constructors

HTTP 
HTTPS 

Instances

Bounded Protocol Source # 
Enum Protocol Source # 
Eq Protocol Source # 
Data Protocol Source # 

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 # 
Read Protocol Source # 
Show Protocol Source # 
Generic Protocol Source # 

Associated Types

type Rep Protocol :: * -> * #

Methods

from :: Protocol -> Rep Protocol x #

to :: Rep Protocol x -> Protocol #

Hashable Protocol Source # 

Methods

hashWithSalt :: Int -> Protocol -> Int #

hash :: Protocol -> Int #

NFData Protocol Source # 

Methods

rnf :: Protocol -> () #

FromXML Protocol Source # 
ToXML Protocol Source # 

Methods

toXML :: Protocol -> XML #

ToHeader Protocol Source # 

Methods

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

ToQuery Protocol Source # 
ToByteString Protocol Source # 

Methods

toBS :: Protocol -> ByteString #

FromText Protocol Source # 
ToText Protocol Source # 

Methods

toText :: Protocol -> Text #

type Rep Protocol Source # 
type Rep Protocol = D1 * (MetaData "Protocol" "Network.AWS.S3.Types.Sum" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" False) ((:+:) * (C1 * (MetaCons "HTTP" PrefixI False) (U1 *)) (C1 * (MetaCons "HTTPS" PrefixI False) (U1 *)))

QuoteFields

data QuoteFields Source #

Constructors

ASNeeded 
Always 

Instances

Bounded QuoteFields Source # 
Enum QuoteFields Source # 
Eq QuoteFields Source # 
Data QuoteFields Source # 

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 # 
Read QuoteFields Source # 
Show QuoteFields Source # 
Generic QuoteFields Source # 

Associated Types

type Rep QuoteFields :: * -> * #

Hashable QuoteFields Source # 
NFData QuoteFields Source # 

Methods

rnf :: QuoteFields -> () #

ToXML QuoteFields Source # 

Methods

toXML :: QuoteFields -> XML #

ToHeader QuoteFields Source # 
ToQuery QuoteFields Source # 
ToByteString QuoteFields Source # 
FromText QuoteFields Source # 
ToText QuoteFields Source # 

Methods

toText :: QuoteFields -> Text #

type Rep QuoteFields Source # 
type Rep QuoteFields = D1 * (MetaData "QuoteFields" "Network.AWS.S3.Types.Sum" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" False) ((:+:) * (C1 * (MetaCons "ASNeeded" PrefixI False) (U1 *)) (C1 * (MetaCons "Always" PrefixI False) (U1 *)))

ReplicationRuleStatus

data ReplicationRuleStatus Source #

Constructors

Disabled 
Enabled 

Instances

Bounded ReplicationRuleStatus Source # 
Enum ReplicationRuleStatus Source # 
Eq ReplicationRuleStatus Source # 
Data ReplicationRuleStatus Source # 

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 # 
Read ReplicationRuleStatus Source # 
Show ReplicationRuleStatus Source # 
Generic ReplicationRuleStatus Source # 
Hashable ReplicationRuleStatus Source # 
NFData ReplicationRuleStatus Source # 

Methods

rnf :: ReplicationRuleStatus -> () #

FromXML ReplicationRuleStatus Source # 
ToXML ReplicationRuleStatus Source # 
ToHeader ReplicationRuleStatus Source # 
ToQuery ReplicationRuleStatus Source # 
ToByteString ReplicationRuleStatus Source # 
FromText ReplicationRuleStatus Source # 
ToText ReplicationRuleStatus Source # 
type Rep ReplicationRuleStatus Source # 
type Rep ReplicationRuleStatus = D1 * (MetaData "ReplicationRuleStatus" "Network.AWS.S3.Types.Sum" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" False) ((:+:) * (C1 * (MetaCons "Disabled" PrefixI False) (U1 *)) (C1 * (MetaCons "Enabled" PrefixI False) (U1 *)))

ReplicationStatus

data ReplicationStatus Source #

Constructors

Completed 
Failed 
Pending 
Replica 

Instances

Bounded ReplicationStatus Source # 
Enum ReplicationStatus Source # 
Eq ReplicationStatus Source # 
Data ReplicationStatus Source # 

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 # 
Read ReplicationStatus Source # 
Show ReplicationStatus Source # 
Generic ReplicationStatus Source # 
Hashable ReplicationStatus Source # 
NFData ReplicationStatus Source # 

Methods

rnf :: ReplicationStatus -> () #

FromXML ReplicationStatus Source # 
ToHeader ReplicationStatus Source # 
ToQuery ReplicationStatus Source # 
ToByteString ReplicationStatus Source # 
FromText ReplicationStatus Source # 
ToText ReplicationStatus Source # 
type Rep ReplicationStatus Source # 
type Rep ReplicationStatus = D1 * (MetaData "ReplicationStatus" "Network.AWS.S3.Types.Sum" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" False) ((:+:) * ((:+:) * (C1 * (MetaCons "Completed" PrefixI False) (U1 *)) (C1 * (MetaCons "Failed" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "Pending" PrefixI False) (U1 *)) (C1 * (MetaCons "Replica" PrefixI False) (U1 *))))

RequestCharged

data RequestCharged Source #

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

Constructors

RCRequester 

Instances

Bounded RequestCharged Source # 
Enum RequestCharged Source # 
Eq RequestCharged Source # 
Data RequestCharged Source # 

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 # 
Read RequestCharged Source # 
Show RequestCharged Source # 
Generic RequestCharged Source # 

Associated Types

type Rep RequestCharged :: * -> * #

Hashable RequestCharged Source # 
NFData RequestCharged Source # 

Methods

rnf :: RequestCharged -> () #

FromXML RequestCharged Source # 
ToHeader RequestCharged Source # 
ToQuery RequestCharged Source # 
ToByteString RequestCharged Source # 
FromText RequestCharged Source # 
ToText RequestCharged Source # 
type Rep RequestCharged Source # 
type Rep RequestCharged = D1 * (MetaData "RequestCharged" "Network.AWS.S3.Types.Sum" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" False) (C1 * (MetaCons "RCRequester" PrefixI False) (U1 *))

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 # 
Enum RequestPayer Source # 
Eq RequestPayer Source # 
Data RequestPayer Source # 

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 # 
Read RequestPayer Source # 
Show RequestPayer Source # 
Generic RequestPayer Source # 

Associated Types

type Rep RequestPayer :: * -> * #

Hashable RequestPayer Source # 
NFData RequestPayer Source # 

Methods

rnf :: RequestPayer -> () #

ToXML RequestPayer Source # 

Methods

toXML :: RequestPayer -> XML #

ToHeader RequestPayer Source # 
ToQuery RequestPayer Source # 
ToByteString RequestPayer Source # 
FromText RequestPayer Source # 
ToText RequestPayer Source # 

Methods

toText :: RequestPayer -> Text #

type Rep RequestPayer Source # 
type Rep RequestPayer = D1 * (MetaData "RequestPayer" "Network.AWS.S3.Types.Sum" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" False) (C1 * (MetaCons "RPRequester" PrefixI False) (U1 *))

RestoreRequestType

data RestoreRequestType Source #

Constructors

Select 

Instances

Bounded RestoreRequestType Source # 
Enum RestoreRequestType Source # 
Eq RestoreRequestType Source # 
Data RestoreRequestType Source # 

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 # 
Read RestoreRequestType Source # 
Show RestoreRequestType Source # 
Generic RestoreRequestType Source # 
Hashable RestoreRequestType Source # 
NFData RestoreRequestType Source # 

Methods

rnf :: RestoreRequestType -> () #

ToXML RestoreRequestType Source # 
ToHeader RestoreRequestType Source # 
ToQuery RestoreRequestType Source # 
ToByteString RestoreRequestType Source # 
FromText RestoreRequestType Source # 
ToText RestoreRequestType Source # 
type Rep RestoreRequestType Source # 
type Rep RestoreRequestType = D1 * (MetaData "RestoreRequestType" "Network.AWS.S3.Types.Sum" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" False) (C1 * (MetaCons "Select" PrefixI False) (U1 *))

ServerSideEncryption

data ServerSideEncryption Source #

Constructors

AES256 
AWSKMS 

Instances

Bounded ServerSideEncryption Source # 
Enum ServerSideEncryption Source # 
Eq ServerSideEncryption Source # 
Data ServerSideEncryption Source # 

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 # 
Read ServerSideEncryption Source # 
Show ServerSideEncryption Source # 
Generic ServerSideEncryption Source # 
Hashable ServerSideEncryption Source # 
NFData ServerSideEncryption Source # 

Methods

rnf :: ServerSideEncryption -> () #

FromXML ServerSideEncryption Source # 
ToXML ServerSideEncryption Source # 
ToHeader ServerSideEncryption Source # 
ToQuery ServerSideEncryption Source # 
ToByteString ServerSideEncryption Source # 
FromText ServerSideEncryption Source # 
ToText ServerSideEncryption Source # 
type Rep ServerSideEncryption Source # 
type Rep ServerSideEncryption = D1 * (MetaData "ServerSideEncryption" "Network.AWS.S3.Types.Sum" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" False) ((:+:) * (C1 * (MetaCons "AES256" PrefixI False) (U1 *)) (C1 * (MetaCons "AWSKMS" PrefixI False) (U1 *)))

SseKMSEncryptedObjectsStatus

data SseKMSEncryptedObjectsStatus Source #

Instances

Bounded SseKMSEncryptedObjectsStatus Source # 
Enum SseKMSEncryptedObjectsStatus Source # 
Eq SseKMSEncryptedObjectsStatus Source # 
Data SseKMSEncryptedObjectsStatus Source # 

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 # 
Read SseKMSEncryptedObjectsStatus Source # 
Show SseKMSEncryptedObjectsStatus Source # 
Generic SseKMSEncryptedObjectsStatus Source # 
Hashable SseKMSEncryptedObjectsStatus Source # 
NFData SseKMSEncryptedObjectsStatus Source # 
FromXML SseKMSEncryptedObjectsStatus Source # 
ToXML SseKMSEncryptedObjectsStatus Source # 
ToHeader SseKMSEncryptedObjectsStatus Source # 
ToQuery SseKMSEncryptedObjectsStatus Source # 
ToByteString SseKMSEncryptedObjectsStatus Source # 
FromText SseKMSEncryptedObjectsStatus Source # 
ToText SseKMSEncryptedObjectsStatus Source # 
type Rep SseKMSEncryptedObjectsStatus Source # 
type Rep SseKMSEncryptedObjectsStatus = D1 * (MetaData "SseKMSEncryptedObjectsStatus" "Network.AWS.S3.Types.Sum" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" False) ((:+:) * (C1 * (MetaCons "SKEOSDisabled" PrefixI False) (U1 *)) (C1 * (MetaCons "SKEOSEnabled" PrefixI False) (U1 *)))

StorageClass

data StorageClass Source #

Instances

Bounded StorageClass Source # 
Enum StorageClass Source # 
Eq StorageClass Source # 
Data StorageClass Source # 

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 # 
Read StorageClass Source # 
Show StorageClass Source # 
Generic StorageClass Source # 

Associated Types

type Rep StorageClass :: * -> * #

Hashable StorageClass Source # 
NFData StorageClass Source # 

Methods

rnf :: StorageClass -> () #

FromXML StorageClass Source # 
ToXML StorageClass Source # 

Methods

toXML :: StorageClass -> XML #

ToHeader StorageClass Source # 
ToQuery StorageClass Source # 
ToByteString StorageClass Source # 
FromText StorageClass Source # 
ToText StorageClass Source # 

Methods

toText :: StorageClass -> Text #

type Rep StorageClass Source # 
type Rep StorageClass = D1 * (MetaData "StorageClass" "Network.AWS.S3.Types.Sum" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" False) ((:+:) * ((:+:) * (C1 * (MetaCons "OnezoneIA" PrefixI False) (U1 *)) (C1 * (MetaCons "ReducedRedundancy" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "Standard" PrefixI False) (U1 *)) (C1 * (MetaCons "StandardIA" PrefixI False) (U1 *))))

StorageClassAnalysisSchemaVersion

data StorageClassAnalysisSchemaVersion Source #

Constructors

V1 

Instances

Bounded StorageClassAnalysisSchemaVersion Source # 
Enum StorageClassAnalysisSchemaVersion Source # 
Eq StorageClassAnalysisSchemaVersion Source # 
Data StorageClassAnalysisSchemaVersion Source # 

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 # 
Read StorageClassAnalysisSchemaVersion Source # 
Show StorageClassAnalysisSchemaVersion Source # 
Generic StorageClassAnalysisSchemaVersion Source # 
Hashable StorageClassAnalysisSchemaVersion Source # 
NFData StorageClassAnalysisSchemaVersion Source # 
FromXML StorageClassAnalysisSchemaVersion Source # 
ToXML StorageClassAnalysisSchemaVersion Source # 
ToHeader StorageClassAnalysisSchemaVersion Source # 
ToQuery StorageClassAnalysisSchemaVersion Source # 
ToByteString StorageClassAnalysisSchemaVersion Source # 
FromText StorageClassAnalysisSchemaVersion Source # 
ToText StorageClassAnalysisSchemaVersion Source # 
type Rep StorageClassAnalysisSchemaVersion Source # 
type Rep StorageClassAnalysisSchemaVersion = D1 * (MetaData "StorageClassAnalysisSchemaVersion" "Network.AWS.S3.Types.Sum" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" False) (C1 * (MetaCons "V1" PrefixI False) (U1 *))

TaggingDirective

data TaggingDirective Source #

Constructors

Copy 
Replace 

Instances

Bounded TaggingDirective Source # 
Enum TaggingDirective Source # 
Eq TaggingDirective Source # 
Data TaggingDirective Source # 

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 # 
Read TaggingDirective Source # 
Show TaggingDirective Source # 
Generic TaggingDirective Source # 
Hashable TaggingDirective Source # 
NFData TaggingDirective Source # 

Methods

rnf :: TaggingDirective -> () #

ToXML TaggingDirective Source # 
ToHeader TaggingDirective Source # 
ToQuery TaggingDirective Source # 
ToByteString TaggingDirective Source # 
FromText TaggingDirective Source # 
ToText TaggingDirective Source # 
type Rep TaggingDirective Source # 
type Rep TaggingDirective = D1 * (MetaData "TaggingDirective" "Network.AWS.S3.Types.Sum" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" False) ((:+:) * (C1 * (MetaCons "Copy" PrefixI False) (U1 *)) (C1 * (MetaCons "Replace" PrefixI False) (U1 *)))

Tier

data Tier Source #

Constructors

TBulk 
TExpedited 
TStandard 

Instances

Bounded Tier Source # 
Enum Tier Source # 

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 # 

Methods

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

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

Data Tier Source # 

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 # 

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 # 
Show Tier Source # 

Methods

showsPrec :: Int -> Tier -> ShowS #

show :: Tier -> String #

showList :: [Tier] -> ShowS #

Generic Tier Source # 

Associated Types

type Rep Tier :: * -> * #

Methods

from :: Tier -> Rep Tier x #

to :: Rep Tier x -> Tier #

Hashable Tier Source # 

Methods

hashWithSalt :: Int -> Tier -> Int #

hash :: Tier -> Int #

NFData Tier Source # 

Methods

rnf :: Tier -> () #

ToXML Tier Source # 

Methods

toXML :: Tier -> XML #

ToHeader Tier Source # 

Methods

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

ToQuery Tier Source # 

Methods

toQuery :: Tier -> QueryString #

ToByteString Tier Source # 

Methods

toBS :: Tier -> ByteString #

FromText Tier Source # 

Methods

parser :: Parser Tier #

ToText Tier Source # 

Methods

toText :: Tier -> Text #

type Rep Tier Source # 
type Rep Tier = D1 * (MetaData "Tier" "Network.AWS.S3.Types.Sum" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" False) ((:+:) * (C1 * (MetaCons "TBulk" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "TExpedited" PrefixI False) (U1 *)) (C1 * (MetaCons "TStandard" PrefixI False) (U1 *))))

TransitionStorageClass

data TransitionStorageClass Source #

Instances

Bounded TransitionStorageClass Source # 
Enum TransitionStorageClass Source # 
Eq TransitionStorageClass Source # 
Data TransitionStorageClass Source # 

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 # 
Read TransitionStorageClass Source # 
Show TransitionStorageClass Source # 
Generic TransitionStorageClass Source # 
Hashable TransitionStorageClass Source # 
NFData TransitionStorageClass Source # 

Methods

rnf :: TransitionStorageClass -> () #

FromXML TransitionStorageClass Source # 
ToXML TransitionStorageClass Source # 
ToHeader TransitionStorageClass Source # 
ToQuery TransitionStorageClass Source # 
ToByteString TransitionStorageClass Source # 
FromText TransitionStorageClass Source # 
ToText TransitionStorageClass Source # 
type Rep TransitionStorageClass Source # 
type Rep TransitionStorageClass = D1 * (MetaData "TransitionStorageClass" "Network.AWS.S3.Types.Sum" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" False) ((:+:) * (C1 * (MetaCons "TSCGlacier" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "TSCOnezoneIA" PrefixI False) (U1 *)) (C1 * (MetaCons "TSCStandardIA" PrefixI False) (U1 *))))

Type

data Type Source #

Instances

Bounded Type Source # 
Enum Type Source # 

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 # 

Methods

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

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

Data Type Source # 

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 # 

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 # 
Show Type Source # 

Methods

showsPrec :: Int -> Type -> ShowS #

show :: Type -> String #

showList :: [Type] -> ShowS #

Generic Type Source # 

Associated Types

type Rep Type :: * -> * #

Methods

from :: Type -> Rep Type x #

to :: Rep Type x -> Type #

Hashable Type Source # 

Methods

hashWithSalt :: Int -> Type -> Int #

hash :: Type -> Int #

NFData Type Source # 

Methods

rnf :: Type -> () #

FromXML Type Source # 

Methods

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

ToXML Type Source # 

Methods

toXML :: Type -> XML #

ToHeader Type Source # 

Methods

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

ToQuery Type Source # 

Methods

toQuery :: Type -> QueryString #

ToByteString Type Source # 

Methods

toBS :: Type -> ByteString #

FromText Type Source # 

Methods

parser :: Parser Type #

ToText Type Source # 

Methods

toText :: Type -> Text #

type Rep Type Source # 
type Rep Type = D1 * (MetaData "Type" "Network.AWS.S3.Types.Sum" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" False) ((:+:) * (C1 * (MetaCons "AmazonCustomerByEmail" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "CanonicalUser" PrefixI False) (U1 *)) (C1 * (MetaCons "Group" PrefixI False) (U1 *))))

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 # 
Data AbortIncompleteMultipartUpload Source # 

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 # 
Show AbortIncompleteMultipartUpload Source # 
Generic AbortIncompleteMultipartUpload Source # 
Hashable AbortIncompleteMultipartUpload Source # 
NFData AbortIncompleteMultipartUpload Source # 
FromXML AbortIncompleteMultipartUpload Source # 
ToXML AbortIncompleteMultipartUpload Source # 
type Rep AbortIncompleteMultipartUpload Source # 
type Rep AbortIncompleteMultipartUpload = D1 * (MetaData "AbortIncompleteMultipartUpload" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" True) (C1 * (MetaCons "AbortIncompleteMultipartUpload'" PrefixI True) (S1 * (MetaSel (Just Symbol "_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 # 
Data AccelerateConfiguration Source # 

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 # 
Show AccelerateConfiguration Source # 
Generic AccelerateConfiguration Source # 
Hashable AccelerateConfiguration Source # 
NFData AccelerateConfiguration Source # 

Methods

rnf :: AccelerateConfiguration -> () #

ToXML AccelerateConfiguration Source # 
type Rep AccelerateConfiguration Source # 
type Rep AccelerateConfiguration = D1 * (MetaData "AccelerateConfiguration" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" True) (C1 * (MetaCons "AccelerateConfiguration'" PrefixI True) (S1 * (MetaSel (Just Symbol "_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 # 
Data AccessControlPolicy Source # 

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 # 
Show AccessControlPolicy Source # 
Generic AccessControlPolicy Source # 
Hashable AccessControlPolicy Source # 
NFData AccessControlPolicy Source # 

Methods

rnf :: AccessControlPolicy -> () #

ToXML AccessControlPolicy Source # 
type Rep AccessControlPolicy Source # 
type Rep AccessControlPolicy = D1 * (MetaData "AccessControlPolicy" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" False) (C1 * (MetaCons "AccessControlPolicy'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_acpGrants") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe [Grant]))) (S1 * (MetaSel (Just Symbol "_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 # 
Data AccessControlTranslation Source # 

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 # 
Show AccessControlTranslation Source # 
Generic AccessControlTranslation Source # 
Hashable AccessControlTranslation Source # 
NFData AccessControlTranslation Source # 
FromXML AccessControlTranslation Source # 
ToXML AccessControlTranslation Source # 
type Rep AccessControlTranslation Source # 
type Rep AccessControlTranslation = D1 * (MetaData "AccessControlTranslation" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" True) (C1 * (MetaCons "AccessControlTranslation'" PrefixI True) (S1 * (MetaSel (Just Symbol "_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 # 
Data AnalyticsAndOperator Source # 

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 # 
Show AnalyticsAndOperator Source # 
Generic AnalyticsAndOperator Source # 
Hashable AnalyticsAndOperator Source # 
NFData AnalyticsAndOperator Source # 

Methods

rnf :: AnalyticsAndOperator -> () #

FromXML AnalyticsAndOperator Source # 
ToXML AnalyticsAndOperator Source # 
type Rep AnalyticsAndOperator Source # 
type Rep AnalyticsAndOperator = D1 * (MetaData "AnalyticsAndOperator" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" False) (C1 * (MetaCons "AnalyticsAndOperator'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_aaoPrefix") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_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 # 
Data AnalyticsConfiguration Source # 

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 # 
Show AnalyticsConfiguration Source # 
Generic AnalyticsConfiguration Source # 
Hashable AnalyticsConfiguration Source # 
NFData AnalyticsConfiguration Source # 

Methods

rnf :: AnalyticsConfiguration -> () #

FromXML AnalyticsConfiguration Source # 
ToXML AnalyticsConfiguration Source # 
type Rep AnalyticsConfiguration Source # 
type Rep AnalyticsConfiguration = D1 * (MetaData "AnalyticsConfiguration" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" False) (C1 * (MetaCons "AnalyticsConfiguration'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_acFilter") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe AnalyticsFilter))) ((:*:) * (S1 * (MetaSel (Just Symbol "_acId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text)) (S1 * (MetaSel (Just Symbol "_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 # 
Data AnalyticsExportDestination Source # 

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 # 
Show AnalyticsExportDestination Source # 
Generic AnalyticsExportDestination Source # 
Hashable AnalyticsExportDestination Source # 
NFData AnalyticsExportDestination Source # 
FromXML AnalyticsExportDestination Source # 
ToXML AnalyticsExportDestination Source # 
type Rep AnalyticsExportDestination Source # 
type Rep AnalyticsExportDestination = D1 * (MetaData "AnalyticsExportDestination" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" True) (C1 * (MetaCons "AnalyticsExportDestination'" PrefixI True) (S1 * (MetaSel (Just Symbol "_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 # 
Data AnalyticsFilter Source # 

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 # 
Show AnalyticsFilter Source # 
Generic AnalyticsFilter Source # 
Hashable AnalyticsFilter Source # 
NFData AnalyticsFilter Source # 

Methods

rnf :: AnalyticsFilter -> () #

FromXML AnalyticsFilter Source # 
ToXML AnalyticsFilter Source # 

Methods

toXML :: AnalyticsFilter -> XML #

type Rep AnalyticsFilter Source # 
type Rep AnalyticsFilter = D1 * (MetaData "AnalyticsFilter" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" False) (C1 * (MetaCons "AnalyticsFilter'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_afTag") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Tag))) ((:*:) * (S1 * (MetaSel (Just Symbol "_afPrefix") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_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 # 
Data AnalyticsS3BucketDestination Source # 

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 # 
Show AnalyticsS3BucketDestination Source # 
Generic AnalyticsS3BucketDestination Source # 
Hashable AnalyticsS3BucketDestination Source # 
NFData AnalyticsS3BucketDestination Source # 
FromXML AnalyticsS3BucketDestination Source # 
ToXML AnalyticsS3BucketDestination Source # 
type Rep AnalyticsS3BucketDestination Source # 
type Rep AnalyticsS3BucketDestination = D1 * (MetaData "AnalyticsS3BucketDestination" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" False) (C1 * (MetaCons "AnalyticsS3BucketDestination'" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_asbdBucketAccountId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_asbdPrefix") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_asbdFormat") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * AnalyticsS3ExportFileFormat)) (S1 * (MetaSel (Just Symbol "_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 # 

Methods

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

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

Data Bucket Source # 

Methods

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

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

toConstr :: Bucket -> Constr #

dataTypeOf :: Bucket -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Bucket Source # 
Show Bucket Source # 
Generic Bucket Source # 

Associated Types

type Rep Bucket :: * -> * #

Methods

from :: Bucket -> Rep Bucket x #

to :: Rep Bucket x -> Bucket #

Hashable Bucket Source # 

Methods

hashWithSalt :: Int -> Bucket -> Int #

hash :: Bucket -> Int #

NFData Bucket Source # 

Methods

rnf :: Bucket -> () #

FromXML Bucket Source # 
type Rep Bucket Source # 
type Rep Bucket = D1 * (MetaData "Bucket" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" False) (C1 * (MetaCons "Bucket'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_bCreationDate") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * RFC822)) (S1 * (MetaSel (Just Symbol "_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 # 
Data BucketLifecycleConfiguration Source # 

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 # 
Show BucketLifecycleConfiguration Source # 
Generic BucketLifecycleConfiguration Source # 
Hashable BucketLifecycleConfiguration Source # 
NFData BucketLifecycleConfiguration Source # 
ToXML BucketLifecycleConfiguration Source # 
type Rep BucketLifecycleConfiguration Source # 
type Rep BucketLifecycleConfiguration = D1 * (MetaData "BucketLifecycleConfiguration" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" True) (C1 * (MetaCons "BucketLifecycleConfiguration'" PrefixI True) (S1 * (MetaSel (Just Symbol "_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 # 
Data BucketLoggingStatus Source # 

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 # 
Show BucketLoggingStatus Source # 
Generic BucketLoggingStatus Source # 
Hashable BucketLoggingStatus Source # 
NFData BucketLoggingStatus Source # 

Methods

rnf :: BucketLoggingStatus -> () #

ToXML BucketLoggingStatus Source # 
type Rep BucketLoggingStatus Source # 
type Rep BucketLoggingStatus = D1 * (MetaData "BucketLoggingStatus" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" True) (C1 * (MetaCons "BucketLoggingStatus'" PrefixI True) (S1 * (MetaSel (Just Symbol "_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 # 
Data CORSConfiguration Source # 

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 # 
Show CORSConfiguration Source # 
Generic CORSConfiguration Source # 
Hashable CORSConfiguration Source # 
NFData CORSConfiguration Source # 

Methods

rnf :: CORSConfiguration -> () #

ToXML CORSConfiguration Source # 
type Rep CORSConfiguration Source # 
type Rep CORSConfiguration = D1 * (MetaData "CORSConfiguration" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" True) (C1 * (MetaCons "CORSConfiguration'" PrefixI True) (S1 * (MetaSel (Just Symbol "_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 # 
Data CORSRule Source # 

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 # 
Show CORSRule Source # 
Generic CORSRule Source # 

Associated Types

type Rep CORSRule :: * -> * #

Methods

from :: CORSRule -> Rep CORSRule x #

to :: Rep CORSRule x -> CORSRule #

Hashable CORSRule Source # 

Methods

hashWithSalt :: Int -> CORSRule -> Int #

hash :: CORSRule -> Int #

NFData CORSRule Source # 

Methods

rnf :: CORSRule -> () #

FromXML CORSRule Source # 
ToXML CORSRule Source # 

Methods

toXML :: CORSRule -> XML #

type Rep CORSRule Source # 
type Rep CORSRule = D1 * (MetaData "CORSRule" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" False) (C1 * (MetaCons "CORSRule'" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_crMaxAgeSeconds") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Int))) (S1 * (MetaSel (Just Symbol "_crAllowedHeaders") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe [Text])))) ((:*:) * (S1 * (MetaSel (Just Symbol "_crExposeHeaders") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe [Text]))) ((:*:) * (S1 * (MetaSel (Just Symbol "_crAllowedMethods") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * [Text])) (S1 * (MetaSel (Just Symbol "_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 # 
Data CSVInput Source # 

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 # 
Show CSVInput Source # 
Generic CSVInput Source # 

Associated Types

type Rep CSVInput :: * -> * #

Methods

from :: CSVInput -> Rep CSVInput x #

to :: Rep CSVInput x -> CSVInput #

Hashable CSVInput Source # 

Methods

hashWithSalt :: Int -> CSVInput -> Int #

hash :: CSVInput -> Int #

NFData CSVInput Source # 

Methods

rnf :: CSVInput -> () #

ToXML CSVInput Source # 

Methods

toXML :: CSVInput -> XML #

type Rep CSVInput Source # 
type Rep CSVInput = D1 * (MetaData "CSVInput" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" False) (C1 * (MetaCons "CSVInput'" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_ciQuoteCharacter") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "_ciRecordDelimiter") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_ciFileHeaderInfo") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe FileHeaderInfo))))) ((:*:) * (S1 * (MetaSel (Just Symbol "_ciQuoteEscapeCharacter") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "_ciComments") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_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 # 
Data CSVOutput Source # 

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 # 
Show CSVOutput Source # 
Generic CSVOutput Source # 

Associated Types

type Rep CSVOutput :: * -> * #

Hashable CSVOutput Source # 
NFData CSVOutput Source # 

Methods

rnf :: CSVOutput -> () #

ToXML CSVOutput Source # 

Methods

toXML :: CSVOutput -> XML #

type Rep CSVOutput Source # 
type Rep CSVOutput = D1 * (MetaData "CSVOutput" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" False) (C1 * (MetaCons "CSVOutput'" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_coQuoteCharacter") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_coQuoteFields") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe QuoteFields)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_coRecordDelimiter") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "_coQuoteEscapeCharacter") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_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 # 
Data CommonPrefix Source # 

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 # 
Show CommonPrefix Source # 
Generic CommonPrefix Source # 

Associated Types

type Rep CommonPrefix :: * -> * #

Hashable CommonPrefix Source # 
NFData CommonPrefix Source # 

Methods

rnf :: CommonPrefix -> () #

FromXML CommonPrefix Source # 
type Rep CommonPrefix Source # 
type Rep CommonPrefix = D1 * (MetaData "CommonPrefix" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" True) (C1 * (MetaCons "CommonPrefix'" PrefixI True) (S1 * (MetaSel (Just Symbol "_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 # 
Data CompletedMultipartUpload Source # 

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 # 
Show CompletedMultipartUpload Source # 
Generic CompletedMultipartUpload Source # 
Hashable CompletedMultipartUpload Source # 
NFData CompletedMultipartUpload Source # 
ToXML CompletedMultipartUpload Source # 
type Rep CompletedMultipartUpload Source # 
type Rep CompletedMultipartUpload = D1 * (MetaData "CompletedMultipartUpload" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" True) (C1 * (MetaCons "CompletedMultipartUpload'" PrefixI True) (S1 * (MetaSel (Just Symbol "_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 # 
Data CompletedPart Source # 

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 # 
Show CompletedPart Source # 
Generic CompletedPart Source # 

Associated Types

type Rep CompletedPart :: * -> * #

Hashable CompletedPart Source # 
NFData CompletedPart Source # 

Methods

rnf :: CompletedPart -> () #

ToXML CompletedPart Source # 

Methods

toXML :: CompletedPart -> XML #

type Rep CompletedPart Source # 
type Rep CompletedPart = D1 * (MetaData "CompletedPart" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" False) (C1 * (MetaCons "CompletedPart'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_cpPartNumber") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Int)) (S1 * (MetaSel (Just Symbol "_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 # 
Data Condition Source # 

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 # 
Show Condition Source # 
Generic Condition Source # 

Associated Types

type Rep Condition :: * -> * #

Hashable Condition Source # 
NFData Condition Source # 

Methods

rnf :: Condition -> () #

FromXML Condition Source # 
ToXML Condition Source # 

Methods

toXML :: Condition -> XML #

type Rep Condition Source # 
type Rep Condition = D1 * (MetaData "Condition" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" False) (C1 * (MetaCons "Condition'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_cKeyPrefixEquals") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_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 # 
Data ContinuationEvent Source # 

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 # 
Show ContinuationEvent Source # 
Generic ContinuationEvent Source # 
Hashable ContinuationEvent Source # 
NFData ContinuationEvent Source # 

Methods

rnf :: ContinuationEvent -> () #

FromXML ContinuationEvent Source # 
type Rep ContinuationEvent Source # 
type Rep ContinuationEvent = D1 * (MetaData "ContinuationEvent" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" False) (C1 * (MetaCons "ContinuationEvent'" PrefixI False) (U1 *))

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 # 
Data CopyObjectResult Source # 

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 # 
Show CopyObjectResult Source # 
Generic CopyObjectResult Source # 
Hashable CopyObjectResult Source # 
NFData CopyObjectResult Source # 

Methods

rnf :: CopyObjectResult -> () #

FromXML CopyObjectResult Source # 
type Rep CopyObjectResult Source # 
type Rep CopyObjectResult = D1 * (MetaData "CopyObjectResult" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" False) (C1 * (MetaCons "CopyObjectResult'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_corETag") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe ETag))) (S1 * (MetaSel (Just Symbol "_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 # 
Data CopyPartResult Source # 

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 # 
Show CopyPartResult Source # 
Generic CopyPartResult Source # 

Associated Types

type Rep CopyPartResult :: * -> * #

Hashable CopyPartResult Source # 
NFData CopyPartResult Source # 

Methods

rnf :: CopyPartResult -> () #

FromXML CopyPartResult Source # 
type Rep CopyPartResult Source # 
type Rep CopyPartResult = D1 * (MetaData "CopyPartResult" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" False) (C1 * (MetaCons "CopyPartResult'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_cprETag") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe ETag))) (S1 * (MetaSel (Just Symbol "_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 # 
Data CreateBucketConfiguration Source # 

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 # 
Show CreateBucketConfiguration Source # 
Generic CreateBucketConfiguration Source # 
Hashable CreateBucketConfiguration Source # 
NFData CreateBucketConfiguration Source # 
ToXML CreateBucketConfiguration Source # 
type Rep CreateBucketConfiguration Source # 
type Rep CreateBucketConfiguration = D1 * (MetaData "CreateBucketConfiguration" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" True) (C1 * (MetaCons "CreateBucketConfiguration'" PrefixI True) (S1 * (MetaSel (Just Symbol "_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 # 

Methods

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

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

Data Delete Source # 

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 # 
Show Delete Source # 
Generic Delete Source # 

Associated Types

type Rep Delete :: * -> * #

Methods

from :: Delete -> Rep Delete x #

to :: Rep Delete x -> Delete #

Hashable Delete Source # 

Methods

hashWithSalt :: Int -> Delete -> Int #

hash :: Delete -> Int #

NFData Delete Source # 

Methods

rnf :: Delete -> () #

ToXML Delete Source # 

Methods

toXML :: Delete -> XML #

type Rep Delete Source # 
type Rep Delete = D1 * (MetaData "Delete" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" False) (C1 * (MetaCons "Delete'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_dQuiet") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Bool))) (S1 * (MetaSel (Just Symbol "_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 # 
Data DeleteMarkerEntry Source # 

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 # 
Show DeleteMarkerEntry Source # 
Generic DeleteMarkerEntry Source # 
Hashable DeleteMarkerEntry Source # 
NFData DeleteMarkerEntry Source # 

Methods

rnf :: DeleteMarkerEntry -> () #

FromXML DeleteMarkerEntry Source # 
type Rep DeleteMarkerEntry Source # 
type Rep DeleteMarkerEntry = D1 * (MetaData "DeleteMarkerEntry" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" False) (C1 * (MetaCons "DeleteMarkerEntry'" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_dmeVersionId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe ObjectVersionId))) (S1 * (MetaSel (Just Symbol "_dmeIsLatest") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Bool)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_dmeOwner") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Owner))) ((:*:) * (S1 * (MetaSel (Just Symbol "_dmeKey") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe ObjectKey))) (S1 * (MetaSel (Just Symbol "_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 # 
Data DeletedObject Source # 

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 # 
Show DeletedObject Source # 
Generic DeletedObject Source # 

Associated Types

type Rep DeletedObject :: * -> * #

Hashable DeletedObject Source # 
NFData DeletedObject Source # 

Methods

rnf :: DeletedObject -> () #

FromXML DeletedObject Source # 
type Rep DeletedObject Source # 
type Rep DeletedObject = D1 * (MetaData "DeletedObject" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" False) (C1 * (MetaCons "DeletedObject'" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_dVersionId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe ObjectVersionId))) (S1 * (MetaSel (Just Symbol "_dDeleteMarker") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Bool)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_dDeleteMarkerVersionId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_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 # 
Data Destination Source # 

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 # 
Show Destination Source # 
Generic Destination Source # 

Associated Types

type Rep Destination :: * -> * #

Hashable Destination Source # 
NFData Destination Source # 

Methods

rnf :: Destination -> () #

FromXML Destination Source # 
ToXML Destination Source # 

Methods

toXML :: Destination -> XML #

type Rep Destination Source # 
type Rep Destination = D1 * (MetaData "Destination" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" False) (C1 * (MetaCons "Destination'" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_dAccessControlTranslation") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe AccessControlTranslation))) (S1 * (MetaSel (Just Symbol "_dAccount") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_dStorageClass") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe StorageClass))) ((:*:) * (S1 * (MetaSel (Just Symbol "_dEncryptionConfiguration") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe EncryptionConfiguration))) (S1 * (MetaSel (Just Symbol "_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 # 
Data Encryption Source # 

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 # 
Generic Encryption Source # 

Associated Types

type Rep Encryption :: * -> * #

Hashable Encryption Source # 
NFData Encryption Source # 

Methods

rnf :: Encryption -> () #

ToXML Encryption Source # 

Methods

toXML :: Encryption -> XML #

type Rep Encryption Source # 
type Rep Encryption = D1 * (MetaData "Encryption" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" False) (C1 * (MetaCons "Encryption'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_eKMSKeyId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe (Sensitive Text)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_eKMSContext") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_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 # 
Data EncryptionConfiguration Source # 

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 # 
Show EncryptionConfiguration Source # 
Generic EncryptionConfiguration Source # 
Hashable EncryptionConfiguration Source # 
NFData EncryptionConfiguration Source # 

Methods

rnf :: EncryptionConfiguration -> () #

FromXML EncryptionConfiguration Source # 
ToXML EncryptionConfiguration Source # 
type Rep EncryptionConfiguration Source # 
type Rep EncryptionConfiguration = D1 * (MetaData "EncryptionConfiguration" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" True) (C1 * (MetaCons "EncryptionConfiguration'" PrefixI True) (S1 * (MetaSel (Just Symbol "_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 # 
Data EndEvent Source # 

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 # 
Show EndEvent Source # 
Generic EndEvent Source # 

Associated Types

type Rep EndEvent :: * -> * #

Methods

from :: EndEvent -> Rep EndEvent x #

to :: Rep EndEvent x -> EndEvent #

Hashable EndEvent Source # 

Methods

hashWithSalt :: Int -> EndEvent -> Int #

hash :: EndEvent -> Int #

NFData EndEvent Source # 

Methods

rnf :: EndEvent -> () #

FromXML EndEvent Source # 
type Rep EndEvent Source # 
type Rep EndEvent = D1 * (MetaData "EndEvent" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" False) (C1 * (MetaCons "EndEvent'" PrefixI False) (U1 *))

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 # 
Data ErrorDocument Source # 

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 # 
Show ErrorDocument Source # 
Generic ErrorDocument Source # 

Associated Types

type Rep ErrorDocument :: * -> * #

Hashable ErrorDocument Source # 
NFData ErrorDocument Source # 

Methods

rnf :: ErrorDocument -> () #

FromXML ErrorDocument Source # 
ToXML ErrorDocument Source # 

Methods

toXML :: ErrorDocument -> XML #

type Rep ErrorDocument Source # 
type Rep ErrorDocument = D1 * (MetaData "ErrorDocument" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" True) (C1 * (MetaCons "ErrorDocument'" PrefixI True) (S1 * (MetaSel (Just Symbol "_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 # 
Data FilterRule Source # 

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 # 
Show FilterRule Source # 
Generic FilterRule Source # 

Associated Types

type Rep FilterRule :: * -> * #

Hashable FilterRule Source # 
NFData FilterRule Source # 

Methods

rnf :: FilterRule -> () #

FromXML FilterRule Source # 
ToXML FilterRule Source # 

Methods

toXML :: FilterRule -> XML #

type Rep FilterRule Source # 
type Rep FilterRule = D1 * (MetaData "FilterRule" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" False) (C1 * (MetaCons "FilterRule'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_frValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_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 # 
Data GlacierJobParameters Source # 

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 # 
Show GlacierJobParameters Source # 
Generic GlacierJobParameters Source # 
Hashable GlacierJobParameters Source # 
NFData GlacierJobParameters Source # 

Methods

rnf :: GlacierJobParameters -> () #

ToXML GlacierJobParameters Source # 
type Rep GlacierJobParameters Source # 
type Rep GlacierJobParameters = D1 * (MetaData "GlacierJobParameters" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" True) (C1 * (MetaCons "GlacierJobParameters'" PrefixI True) (S1 * (MetaSel (Just Symbol "_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 # 

Methods

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

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

Data Grant Source # 

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 # 
Show Grant Source # 

Methods

showsPrec :: Int -> Grant -> ShowS #

show :: Grant -> String #

showList :: [Grant] -> ShowS #

Generic Grant Source # 

Associated Types

type Rep Grant :: * -> * #

Methods

from :: Grant -> Rep Grant x #

to :: Rep Grant x -> Grant #

Hashable Grant Source # 

Methods

hashWithSalt :: Int -> Grant -> Int #

hash :: Grant -> Int #

NFData Grant Source # 

Methods

rnf :: Grant -> () #

FromXML Grant Source # 

Methods

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

ToXML Grant Source # 

Methods

toXML :: Grant -> XML #

type Rep Grant Source # 
type Rep Grant = D1 * (MetaData "Grant" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" False) (C1 * (MetaCons "Grant'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_gPermission") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Permission))) (S1 * (MetaSel (Just Symbol "_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 # 

Methods

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

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

Data Grantee Source # 

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 # 
Show Grantee Source # 
Generic Grantee Source # 

Associated Types

type Rep Grantee :: * -> * #

Methods

from :: Grantee -> Rep Grantee x #

to :: Rep Grantee x -> Grantee #

Hashable Grantee Source # 

Methods

hashWithSalt :: Int -> Grantee -> Int #

hash :: Grantee -> Int #

NFData Grantee Source # 

Methods

rnf :: Grantee -> () #

FromXML Grantee Source # 
ToXML Grantee Source # 

Methods

toXML :: Grantee -> XML #

type Rep Grantee Source # 

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 # 
Data IndexDocument Source # 

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 # 
Show IndexDocument Source # 
Generic IndexDocument Source # 

Associated Types

type Rep IndexDocument :: * -> * #

Hashable IndexDocument Source # 
NFData IndexDocument Source # 

Methods

rnf :: IndexDocument -> () #

FromXML IndexDocument Source # 
ToXML IndexDocument Source # 

Methods

toXML :: IndexDocument -> XML #

type Rep IndexDocument Source # 
type Rep IndexDocument = D1 * (MetaData "IndexDocument" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" True) (C1 * (MetaCons "IndexDocument'" PrefixI True) (S1 * (MetaSel (Just Symbol "_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 # 
Data Initiator Source # 

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 # 
Show Initiator Source # 
Generic Initiator Source # 

Associated Types

type Rep Initiator :: * -> * #

Hashable Initiator Source # 
NFData Initiator Source # 

Methods

rnf :: Initiator -> () #

FromXML Initiator Source # 
type Rep Initiator Source # 
type Rep Initiator = D1 * (MetaData "Initiator" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" False) (C1 * (MetaCons "Initiator'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_iDisplayName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_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 # 
Data InputSerialization Source # 

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 # 
Show InputSerialization Source # 
Generic InputSerialization Source # 
Hashable InputSerialization Source # 
NFData InputSerialization Source # 

Methods

rnf :: InputSerialization -> () #

ToXML InputSerialization Source # 
type Rep InputSerialization Source # 
type Rep InputSerialization = D1 * (MetaData "InputSerialization" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" False) (C1 * (MetaCons "InputSerialization'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_isJSON") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe JSONInput))) ((:*:) * (S1 * (MetaSel (Just Symbol "_isCSV") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe CSVInput))) (S1 * (MetaSel (Just Symbol "_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 # 
Data InventoryConfiguration Source # 

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 # 
Generic InventoryConfiguration Source # 
Hashable InventoryConfiguration Source # 
NFData InventoryConfiguration Source # 

Methods

rnf :: InventoryConfiguration -> () #

FromXML InventoryConfiguration Source # 
ToXML InventoryConfiguration Source # 
type Rep InventoryConfiguration Source # 

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 # 
Data InventoryDestination Source # 

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 # 
Generic InventoryDestination Source # 
Hashable InventoryDestination Source # 
NFData InventoryDestination Source # 

Methods

rnf :: InventoryDestination -> () #

FromXML InventoryDestination Source # 
ToXML InventoryDestination Source # 
type Rep InventoryDestination Source # 
type Rep InventoryDestination = D1 * (MetaData "InventoryDestination" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" True) (C1 * (MetaCons "InventoryDestination'" PrefixI True) (S1 * (MetaSel (Just Symbol "_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 # 
Data InventoryEncryption Source # 

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 # 
Generic InventoryEncryption Source # 
Hashable InventoryEncryption Source # 
NFData InventoryEncryption Source # 

Methods

rnf :: InventoryEncryption -> () #

FromXML InventoryEncryption Source # 
ToXML InventoryEncryption Source # 
type Rep InventoryEncryption Source # 
type Rep InventoryEncryption = D1 * (MetaData "InventoryEncryption" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" False) (C1 * (MetaCons "InventoryEncryption'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_ieSSES3") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe SSES3))) (S1 * (MetaSel (Just Symbol "_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 # 
Data InventoryFilter Source # 

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 # 
Show InventoryFilter Source # 
Generic InventoryFilter Source # 
Hashable InventoryFilter Source # 
NFData InventoryFilter Source # 

Methods

rnf :: InventoryFilter -> () #

FromXML InventoryFilter Source # 
ToXML InventoryFilter Source # 

Methods

toXML :: InventoryFilter -> XML #

type Rep InventoryFilter Source # 
type Rep InventoryFilter = D1 * (MetaData "InventoryFilter" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" True) (C1 * (MetaCons "InventoryFilter'" PrefixI True) (S1 * (MetaSel (Just Symbol "_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 # 
Data InventoryS3BucketDestination Source # 

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 # 
Generic InventoryS3BucketDestination Source # 
Hashable InventoryS3BucketDestination Source # 
NFData InventoryS3BucketDestination Source # 
FromXML InventoryS3BucketDestination Source # 
ToXML InventoryS3BucketDestination Source # 
type Rep InventoryS3BucketDestination Source # 
type Rep InventoryS3BucketDestination = D1 * (MetaData "InventoryS3BucketDestination" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" False) (C1 * (MetaCons "InventoryS3BucketDestination'" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_isbdPrefix") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_isbdAccountId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_isbdEncryption") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe InventoryEncryption))) ((:*:) * (S1 * (MetaSel (Just Symbol "_isbdBucket") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * BucketName)) (S1 * (MetaSel (Just Symbol "_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 # 
Data InventorySchedule Source # 

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 # 
Show InventorySchedule Source # 
Generic InventorySchedule Source # 
Hashable InventorySchedule Source # 
NFData InventorySchedule Source # 

Methods

rnf :: InventorySchedule -> () #

FromXML InventorySchedule Source # 
ToXML InventorySchedule Source # 
type Rep InventorySchedule Source # 
type Rep InventorySchedule = D1 * (MetaData "InventorySchedule" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" True) (C1 * (MetaCons "InventorySchedule'" PrefixI True) (S1 * (MetaSel (Just Symbol "_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 # 
Data JSONInput Source # 

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 # 
Show JSONInput Source # 
Generic JSONInput Source # 

Associated Types

type Rep JSONInput :: * -> * #

Hashable JSONInput Source # 
NFData JSONInput Source # 

Methods

rnf :: JSONInput -> () #

ToXML JSONInput Source # 

Methods

toXML :: JSONInput -> XML #

type Rep JSONInput Source # 
type Rep JSONInput = D1 * (MetaData "JSONInput" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" True) (C1 * (MetaCons "JSONInput'" PrefixI True) (S1 * (MetaSel (Just Symbol "_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 # 
Data JSONOutput Source # 

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 # 
Show JSONOutput Source # 
Generic JSONOutput Source # 

Associated Types

type Rep JSONOutput :: * -> * #

Hashable JSONOutput Source # 
NFData JSONOutput Source # 

Methods

rnf :: JSONOutput -> () #

ToXML JSONOutput Source # 

Methods

toXML :: JSONOutput -> XML #

type Rep JSONOutput Source # 
type Rep JSONOutput = D1 * (MetaData "JSONOutput" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" True) (C1 * (MetaCons "JSONOutput'" PrefixI True) (S1 * (MetaSel (Just Symbol "_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 # 
Data LambdaFunctionConfiguration Source # 

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 # 
Show LambdaFunctionConfiguration Source # 
Generic LambdaFunctionConfiguration Source # 
Hashable LambdaFunctionConfiguration Source # 
NFData LambdaFunctionConfiguration Source # 
FromXML LambdaFunctionConfiguration Source # 
ToXML LambdaFunctionConfiguration Source # 
type Rep LambdaFunctionConfiguration Source # 
type Rep LambdaFunctionConfiguration = D1 * (MetaData "LambdaFunctionConfiguration" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" False) (C1 * (MetaCons "LambdaFunctionConfiguration'" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_lfcId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_lfcFilter") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe NotificationConfigurationFilter)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_lfcLambdaFunctionARN") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text)) (S1 * (MetaSel (Just Symbol "_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 # 
Data LifecycleExpiration Source # 

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 # 
Show LifecycleExpiration Source # 
Generic LifecycleExpiration Source # 
Hashable LifecycleExpiration Source # 
NFData LifecycleExpiration Source # 

Methods

rnf :: LifecycleExpiration -> () #

FromXML LifecycleExpiration Source # 
ToXML LifecycleExpiration Source # 
type Rep LifecycleExpiration Source # 
type Rep LifecycleExpiration = D1 * (MetaData "LifecycleExpiration" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" False) (C1 * (MetaCons "LifecycleExpiration'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_leDays") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Int))) ((:*:) * (S1 * (MetaSel (Just Symbol "_leDate") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe RFC822))) (S1 * (MetaSel (Just Symbol "_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 # 
Data LifecycleRule Source # 

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 # 
Show LifecycleRule Source # 
Generic LifecycleRule Source # 

Associated Types

type Rep LifecycleRule :: * -> * #

Hashable LifecycleRule Source # 
NFData LifecycleRule Source # 

Methods

rnf :: LifecycleRule -> () #

FromXML LifecycleRule Source # 
ToXML LifecycleRule Source # 

Methods

toXML :: LifecycleRule -> XML #

type Rep LifecycleRule Source # 

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 # 
Data LifecycleRuleAndOperator Source # 

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 # 
Show LifecycleRuleAndOperator Source # 
Generic LifecycleRuleAndOperator Source # 
Hashable LifecycleRuleAndOperator Source # 
NFData LifecycleRuleAndOperator Source # 
FromXML LifecycleRuleAndOperator Source # 
ToXML LifecycleRuleAndOperator Source # 
type Rep LifecycleRuleAndOperator Source # 
type Rep LifecycleRuleAndOperator = D1 * (MetaData "LifecycleRuleAndOperator" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" False) (C1 * (MetaCons "LifecycleRuleAndOperator'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_lraoPrefix") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_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 # 
Data LifecycleRuleFilter Source # 

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 # 
Show LifecycleRuleFilter Source # 
Generic LifecycleRuleFilter Source # 
Hashable LifecycleRuleFilter Source # 
NFData LifecycleRuleFilter Source # 

Methods

rnf :: LifecycleRuleFilter -> () #

FromXML LifecycleRuleFilter Source # 
ToXML LifecycleRuleFilter Source # 
type Rep LifecycleRuleFilter Source # 
type Rep LifecycleRuleFilter = D1 * (MetaData "LifecycleRuleFilter" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" False) (C1 * (MetaCons "LifecycleRuleFilter'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_lrfTag") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Tag))) ((:*:) * (S1 * (MetaSel (Just Symbol "_lrfPrefix") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_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 # 
Data LoggingEnabled Source # 

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 # 
Show LoggingEnabled Source # 
Generic LoggingEnabled Source # 

Associated Types

type Rep LoggingEnabled :: * -> * #

Hashable LoggingEnabled Source # 
NFData LoggingEnabled Source # 

Methods

rnf :: LoggingEnabled -> () #

FromXML LoggingEnabled Source # 
ToXML LoggingEnabled Source # 

Methods

toXML :: LoggingEnabled -> XML #

type Rep LoggingEnabled Source # 
type Rep LoggingEnabled = D1 * (MetaData "LoggingEnabled" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" False) (C1 * (MetaCons "LoggingEnabled'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_leTargetGrants") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe [TargetGrant]))) ((:*:) * (S1 * (MetaSel (Just Symbol "_leTargetBucket") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text)) (S1 * (MetaSel (Just Symbol "_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 # 
Data MetadataEntry Source # 

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 # 
Show MetadataEntry Source # 
Generic MetadataEntry Source # 

Associated Types

type Rep MetadataEntry :: * -> * #

Hashable MetadataEntry Source # 
NFData MetadataEntry Source # 

Methods

rnf :: MetadataEntry -> () #

ToXML MetadataEntry Source # 

Methods

toXML :: MetadataEntry -> XML #

type Rep MetadataEntry Source # 
type Rep MetadataEntry = D1 * (MetaData "MetadataEntry" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" False) (C1 * (MetaCons "MetadataEntry'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_meValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_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 # 
Data MetricsAndOperator Source # 

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 # 
Show MetricsAndOperator Source # 
Generic MetricsAndOperator Source # 
Hashable MetricsAndOperator Source # 
NFData MetricsAndOperator Source # 

Methods

rnf :: MetricsAndOperator -> () #

FromXML MetricsAndOperator Source # 
ToXML MetricsAndOperator Source # 
type Rep MetricsAndOperator Source # 
type Rep MetricsAndOperator = D1 * (MetaData "MetricsAndOperator" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" False) (C1 * (MetaCons "MetricsAndOperator'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_maoPrefix") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_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 # 
Data MetricsConfiguration Source # 

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 # 
Show MetricsConfiguration Source # 
Generic MetricsConfiguration Source # 
Hashable MetricsConfiguration Source # 
NFData MetricsConfiguration Source # 

Methods

rnf :: MetricsConfiguration -> () #

FromXML MetricsConfiguration Source # 
ToXML MetricsConfiguration Source # 
type Rep MetricsConfiguration Source # 
type Rep MetricsConfiguration = D1 * (MetaData "MetricsConfiguration" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" False) (C1 * (MetaCons "MetricsConfiguration'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_mcFilter") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe MetricsFilter))) (S1 * (MetaSel (Just Symbol "_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 # 
Data MetricsFilter Source # 

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 # 
Show MetricsFilter Source # 
Generic MetricsFilter Source # 

Associated Types

type Rep MetricsFilter :: * -> * #

Hashable MetricsFilter Source # 
NFData MetricsFilter Source # 

Methods

rnf :: MetricsFilter -> () #

FromXML MetricsFilter Source # 
ToXML MetricsFilter Source # 

Methods

toXML :: MetricsFilter -> XML #

type Rep MetricsFilter Source # 
type Rep MetricsFilter = D1 * (MetaData "MetricsFilter" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" False) (C1 * (MetaCons "MetricsFilter'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_mfTag") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Tag))) ((:*:) * (S1 * (MetaSel (Just Symbol "_mfPrefix") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_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 # 
Data MultipartUpload Source # 

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 # 
Show MultipartUpload Source # 
Generic MultipartUpload Source # 
Hashable MultipartUpload Source # 
NFData MultipartUpload Source # 

Methods

rnf :: MultipartUpload -> () #

FromXML MultipartUpload Source # 
type Rep MultipartUpload Source # 

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 # 
Data NoncurrentVersionExpiration Source # 

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 # 
Show NoncurrentVersionExpiration Source # 
Generic NoncurrentVersionExpiration Source # 
Hashable NoncurrentVersionExpiration Source # 
NFData NoncurrentVersionExpiration Source # 
FromXML NoncurrentVersionExpiration Source # 
ToXML NoncurrentVersionExpiration Source # 
type Rep NoncurrentVersionExpiration Source # 
type Rep NoncurrentVersionExpiration = D1 * (MetaData "NoncurrentVersionExpiration" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" True) (C1 * (MetaCons "NoncurrentVersionExpiration'" PrefixI True) (S1 * (MetaSel (Just Symbol "_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 # 
Data NoncurrentVersionTransition Source # 

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 # 
Show NoncurrentVersionTransition Source # 
Generic NoncurrentVersionTransition Source # 
Hashable NoncurrentVersionTransition Source # 
NFData NoncurrentVersionTransition Source # 
FromXML NoncurrentVersionTransition Source # 
ToXML NoncurrentVersionTransition Source # 
type Rep NoncurrentVersionTransition Source # 
type Rep NoncurrentVersionTransition = D1 * (MetaData "NoncurrentVersionTransition" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" False) (C1 * (MetaCons "NoncurrentVersionTransition'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_nvtNoncurrentDays") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Int)) (S1 * (MetaSel (Just Symbol "_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 # 
Data NotificationConfiguration Source # 

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 # 
Show NotificationConfiguration Source # 
Generic NotificationConfiguration Source # 
Hashable NotificationConfiguration Source # 
NFData NotificationConfiguration Source # 
FromXML NotificationConfiguration Source # 
ToXML NotificationConfiguration Source # 
type Rep NotificationConfiguration Source # 
type Rep NotificationConfiguration = D1 * (MetaData "NotificationConfiguration" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" False) (C1 * (MetaCons "NotificationConfiguration'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_ncQueueConfigurations") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe [QueueConfiguration]))) ((:*:) * (S1 * (MetaSel (Just Symbol "_ncTopicConfigurations") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe [TopicConfiguration]))) (S1 * (MetaSel (Just Symbol "_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 # 
Data NotificationConfigurationFilter Source # 

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 # 
Show NotificationConfigurationFilter Source # 
Generic NotificationConfigurationFilter Source # 
Hashable NotificationConfigurationFilter Source # 
NFData NotificationConfigurationFilter Source # 
FromXML NotificationConfigurationFilter Source # 
ToXML NotificationConfigurationFilter Source # 
type Rep NotificationConfigurationFilter Source # 
type Rep NotificationConfigurationFilter = D1 * (MetaData "NotificationConfigurationFilter" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" True) (C1 * (MetaCons "NotificationConfigurationFilter'" PrefixI True) (S1 * (MetaSel (Just Symbol "_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 # 

Methods

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

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

Data Object Source # 

Methods

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

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

toConstr :: Object -> Constr #

dataTypeOf :: Object -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Object Source # 
Show Object Source # 
Generic Object Source # 

Associated Types

type Rep Object :: * -> * #

Methods

from :: Object -> Rep Object x #

to :: Rep Object x -> Object #

Hashable Object Source # 

Methods

hashWithSalt :: Int -> Object -> Int #

hash :: Object -> Int #

NFData Object Source # 

Methods

rnf :: Object -> () #

FromXML Object Source # 
type Rep Object Source # 

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 # 
Data ObjectIdentifier Source # 

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 # 
Show ObjectIdentifier Source # 
Generic ObjectIdentifier Source # 
Hashable ObjectIdentifier Source # 
NFData ObjectIdentifier Source # 

Methods

rnf :: ObjectIdentifier -> () #

ToXML ObjectIdentifier Source # 
type Rep ObjectIdentifier Source # 
type Rep ObjectIdentifier = D1 * (MetaData "ObjectIdentifier" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" False) (C1 * (MetaCons "ObjectIdentifier'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_oiVersionId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe ObjectVersionId))) (S1 * (MetaSel (Just Symbol "_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 # 
Data ObjectVersion Source # 

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 # 
Show ObjectVersion Source # 
Generic ObjectVersion Source # 

Associated Types

type Rep ObjectVersion :: * -> * #

Hashable ObjectVersion Source # 
NFData ObjectVersion Source # 

Methods

rnf :: ObjectVersion -> () #

FromXML ObjectVersion Source # 
type Rep ObjectVersion Source # 

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 # 
Data OutputLocation Source # 

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 # 
Generic OutputLocation Source # 

Associated Types

type Rep OutputLocation :: * -> * #

Hashable OutputLocation Source # 
NFData OutputLocation Source # 

Methods

rnf :: OutputLocation -> () #

ToXML OutputLocation Source # 

Methods

toXML :: OutputLocation -> XML #

type Rep OutputLocation Source # 
type Rep OutputLocation = D1 * (MetaData "OutputLocation" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" True) (C1 * (MetaCons "OutputLocation'" PrefixI True) (S1 * (MetaSel (Just Symbol "_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 # 
Data OutputSerialization Source # 

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 # 
Show OutputSerialization Source # 
Generic OutputSerialization Source # 
Hashable OutputSerialization Source # 
NFData OutputSerialization Source # 

Methods

rnf :: OutputSerialization -> () #

ToXML OutputSerialization Source # 
type Rep OutputSerialization Source # 
type Rep OutputSerialization = D1 * (MetaData "OutputSerialization" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" False) (C1 * (MetaCons "OutputSerialization'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_osJSON") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe JSONOutput))) (S1 * (MetaSel (Just Symbol "_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 # 

Methods

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

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

Data Owner Source # 

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 # 
Show Owner Source # 

Methods

showsPrec :: Int -> Owner -> ShowS #

show :: Owner -> String #

showList :: [Owner] -> ShowS #

Generic Owner Source # 

Associated Types

type Rep Owner :: * -> * #

Methods

from :: Owner -> Rep Owner x #

to :: Rep Owner x -> Owner #

Hashable Owner Source # 

Methods

hashWithSalt :: Int -> Owner -> Int #

hash :: Owner -> Int #

NFData Owner Source # 

Methods

rnf :: Owner -> () #

FromXML Owner Source # 

Methods

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

ToXML Owner Source # 

Methods

toXML :: Owner -> XML #

type Rep Owner Source # 
type Rep Owner = D1 * (MetaData "Owner" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" False) (C1 * (MetaCons "Owner'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_oDisplayName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_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 # 

Methods

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

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

Data Part Source # 

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 # 
Show Part Source # 

Methods

showsPrec :: Int -> Part -> ShowS #

show :: Part -> String #

showList :: [Part] -> ShowS #

Generic Part Source # 

Associated Types

type Rep Part :: * -> * #

Methods

from :: Part -> Rep Part x #

to :: Rep Part x -> Part #

Hashable Part Source # 

Methods

hashWithSalt :: Int -> Part -> Int #

hash :: Part -> Int #

NFData Part Source # 

Methods

rnf :: Part -> () #

FromXML Part Source # 

Methods

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

type Rep Part Source # 
type Rep Part = D1 * (MetaData "Part" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" False) (C1 * (MetaCons "Part'" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_pETag") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe ETag))) (S1 * (MetaSel (Just Symbol "_pSize") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Int)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_pPartNumber") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Int))) (S1 * (MetaSel (Just Symbol "_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 # 
Data Progress Source # 

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 # 
Show Progress Source # 
Generic Progress Source # 

Associated Types

type Rep Progress :: * -> * #

Methods

from :: Progress -> Rep Progress x #

to :: Rep Progress x -> Progress #

Hashable Progress Source # 

Methods

hashWithSalt :: Int -> Progress -> Int #

hash :: Progress -> Int #

NFData Progress Source # 

Methods

rnf :: Progress -> () #

FromXML Progress Source # 
type Rep Progress Source # 
type Rep Progress = D1 * (MetaData "Progress" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" False) (C1 * (MetaCons "Progress'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_pBytesReturned") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Integer))) ((:*:) * (S1 * (MetaSel (Just Symbol "_pBytesScanned") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Integer))) (S1 * (MetaSel (Just Symbol "_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 # 
Data ProgressEvent Source # 

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 # 
Show ProgressEvent Source # 
Generic ProgressEvent Source # 

Associated Types

type Rep ProgressEvent :: * -> * #

Hashable ProgressEvent Source # 
NFData ProgressEvent Source # 

Methods

rnf :: ProgressEvent -> () #

FromXML ProgressEvent Source # 
type Rep ProgressEvent Source # 
type Rep ProgressEvent = D1 * (MetaData "ProgressEvent" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" True) (C1 * (MetaCons "ProgressEvent'" PrefixI True) (S1 * (MetaSel (Just Symbol "_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 # 
Data QueueConfiguration Source # 

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 # 
Show QueueConfiguration Source # 
Generic QueueConfiguration Source # 
Hashable QueueConfiguration Source # 
NFData QueueConfiguration Source # 

Methods

rnf :: QueueConfiguration -> () #

FromXML QueueConfiguration Source # 
ToXML QueueConfiguration Source # 
type Rep QueueConfiguration Source # 
type Rep QueueConfiguration = D1 * (MetaData "QueueConfiguration" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" False) (C1 * (MetaCons "QueueConfiguration'" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_qcId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_qcFilter") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe NotificationConfigurationFilter)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_qcQueueARN") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text)) (S1 * (MetaSel (Just Symbol "_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 # 
Data RecordsEvent Source # 

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 # 
Show RecordsEvent Source # 
Generic RecordsEvent Source # 

Associated Types

type Rep RecordsEvent :: * -> * #

Hashable RecordsEvent Source # 
NFData RecordsEvent Source # 

Methods

rnf :: RecordsEvent -> () #

FromXML RecordsEvent Source # 
type Rep RecordsEvent Source # 
type Rep RecordsEvent = D1 * (MetaData "RecordsEvent" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" True) (C1 * (MetaCons "RecordsEvent'" PrefixI True) (S1 * (MetaSel (Just Symbol "_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 # 
Data Redirect Source # 

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 # 
Show Redirect Source # 
Generic Redirect Source # 

Associated Types

type Rep Redirect :: * -> * #

Methods

from :: Redirect -> Rep Redirect x #

to :: Rep Redirect x -> Redirect #

Hashable Redirect Source # 

Methods

hashWithSalt :: Int -> Redirect -> Int #

hash :: Redirect -> Int #

NFData Redirect Source # 

Methods

rnf :: Redirect -> () #

FromXML Redirect Source # 
ToXML Redirect Source # 

Methods

toXML :: Redirect -> XML #

type Rep Redirect Source # 
type Rep Redirect = D1 * (MetaData "Redirect" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" False) (C1 * (MetaCons "Redirect'" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_rHostName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_rProtocol") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Protocol)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_rHTTPRedirectCode") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "_rReplaceKeyWith") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_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 # 
Data RedirectAllRequestsTo Source # 

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 # 
Show RedirectAllRequestsTo Source # 
Generic RedirectAllRequestsTo Source # 
Hashable RedirectAllRequestsTo Source # 
NFData RedirectAllRequestsTo Source # 

Methods

rnf :: RedirectAllRequestsTo -> () #

FromXML RedirectAllRequestsTo Source # 
ToXML RedirectAllRequestsTo Source # 
type Rep RedirectAllRequestsTo Source # 
type Rep RedirectAllRequestsTo = D1 * (MetaData "RedirectAllRequestsTo" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" False) (C1 * (MetaCons "RedirectAllRequestsTo'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_rartProtocol") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Protocol))) (S1 * (MetaSel (Just Symbol "_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 # 
Data ReplicationConfiguration Source # 

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 # 
Show ReplicationConfiguration Source # 
Generic ReplicationConfiguration Source # 
Hashable ReplicationConfiguration Source # 
NFData ReplicationConfiguration Source # 
FromXML ReplicationConfiguration Source # 
ToXML ReplicationConfiguration Source # 
type Rep ReplicationConfiguration Source # 
type Rep ReplicationConfiguration = D1 * (MetaData "ReplicationConfiguration" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" False) (C1 * (MetaCons "ReplicationConfiguration'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_rcRole") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text)) (S1 * (MetaSel (Just Symbol "_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 # 
Data ReplicationRule Source # 

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 # 
Show ReplicationRule Source # 
Generic ReplicationRule Source # 
Hashable ReplicationRule Source # 
NFData ReplicationRule Source # 

Methods

rnf :: ReplicationRule -> () #

FromXML ReplicationRule Source # 
ToXML ReplicationRule Source # 

Methods

toXML :: ReplicationRule -> XML #

type Rep ReplicationRule Source # 

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 # 
Data RequestPaymentConfiguration Source # 

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 # 
Show RequestPaymentConfiguration Source # 
Generic RequestPaymentConfiguration Source # 
Hashable RequestPaymentConfiguration Source # 
NFData RequestPaymentConfiguration Source # 
ToXML RequestPaymentConfiguration Source # 
type Rep RequestPaymentConfiguration Source # 
type Rep RequestPaymentConfiguration = D1 * (MetaData "RequestPaymentConfiguration" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" True) (C1 * (MetaCons "RequestPaymentConfiguration'" PrefixI True) (S1 * (MetaSel (Just Symbol "_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 # 
Data RequestProgress Source # 

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 # 
Show RequestProgress Source # 
Generic RequestProgress Source # 
Hashable RequestProgress Source # 
NFData RequestProgress Source # 

Methods

rnf :: RequestProgress -> () #

ToXML RequestProgress Source # 

Methods

toXML :: RequestProgress -> XML #

type Rep RequestProgress Source # 
type Rep RequestProgress = D1 * (MetaData "RequestProgress" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" True) (C1 * (MetaCons "RequestProgress'" PrefixI True) (S1 * (MetaSel (Just Symbol "_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 # 
Data RestoreRequest Source # 

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 # 
Generic RestoreRequest Source # 

Associated Types

type Rep RestoreRequest :: * -> * #

Hashable RestoreRequest Source # 
NFData RestoreRequest Source # 

Methods

rnf :: RestoreRequest -> () #

ToXML RestoreRequest Source # 

Methods

toXML :: RestoreRequest -> XML #

type Rep RestoreRequest Source # 

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 # 
Data RoutingRule Source # 

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 # 
Show RoutingRule Source # 
Generic RoutingRule Source # 

Associated Types

type Rep RoutingRule :: * -> * #

Hashable RoutingRule Source # 
NFData RoutingRule Source # 

Methods

rnf :: RoutingRule -> () #

FromXML RoutingRule Source # 
ToXML RoutingRule Source # 

Methods

toXML :: RoutingRule -> XML #

type Rep RoutingRule Source # 
type Rep RoutingRule = D1 * (MetaData "RoutingRule" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" False) (C1 * (MetaCons "RoutingRule'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_rrCondition") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Condition))) (S1 * (MetaSel (Just Symbol "_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 # 
Data S3KeyFilter Source # 

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 # 
Show S3KeyFilter Source # 
Generic S3KeyFilter Source # 

Associated Types

type Rep S3KeyFilter :: * -> * #

Hashable S3KeyFilter Source # 
NFData S3KeyFilter Source # 

Methods

rnf :: S3KeyFilter -> () #

FromXML S3KeyFilter Source # 
ToXML S3KeyFilter Source # 

Methods

toXML :: S3KeyFilter -> XML #

type Rep S3KeyFilter Source # 
type Rep S3KeyFilter = D1 * (MetaData "S3KeyFilter" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" True) (C1 * (MetaCons "S3KeyFilter'" PrefixI True) (S1 * (MetaSel (Just Symbol "_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 # 
Data S3Location Source # 

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 # 
Generic S3Location Source # 

Associated Types

type Rep S3Location :: * -> * #

Hashable S3Location Source # 
NFData S3Location Source # 

Methods

rnf :: S3Location -> () #

ToXML S3Location Source # 

Methods

toXML :: S3Location -> XML #

type Rep S3Location Source # 

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 # 
Data S3ServiceError Source # 

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 # 
Show S3ServiceError Source # 
Generic S3ServiceError Source # 

Associated Types

type Rep S3ServiceError :: * -> * #

Hashable S3ServiceError Source # 
NFData S3ServiceError Source # 

Methods

rnf :: S3ServiceError -> () #

FromXML S3ServiceError Source # 
type Rep S3ServiceError Source # 
type Rep S3ServiceError = D1 * (MetaData "S3ServiceError" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" False) (C1 * (MetaCons "S3ServiceError'" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_sseVersionId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe ObjectVersionId))) (S1 * (MetaSel (Just Symbol "_sseKey") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe ObjectKey)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_sseCode") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_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 # 

Methods

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

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

Data SSEKMS Source # 

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 # 
Generic SSEKMS Source # 

Associated Types

type Rep SSEKMS :: * -> * #

Methods

from :: SSEKMS -> Rep SSEKMS x #

to :: Rep SSEKMS x -> SSEKMS #

Hashable SSEKMS Source # 

Methods

hashWithSalt :: Int -> SSEKMS -> Int #

hash :: SSEKMS -> Int #

NFData SSEKMS Source # 

Methods

rnf :: SSEKMS -> () #

FromXML SSEKMS Source # 
ToXML SSEKMS Source # 

Methods

toXML :: SSEKMS -> XML #

type Rep SSEKMS Source # 
type Rep SSEKMS = D1 * (MetaData "SSEKMS" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" True) (C1 * (MetaCons "SSEKMS'" PrefixI True) (S1 * (MetaSel (Just Symbol "_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 # 

Methods

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

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

Data SSES3 Source # 

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 # 
Show SSES3 Source # 

Methods

showsPrec :: Int -> SSES3 -> ShowS #

show :: SSES3 -> String #

showList :: [SSES3] -> ShowS #

Generic SSES3 Source # 

Associated Types

type Rep SSES3 :: * -> * #

Methods

from :: SSES3 -> Rep SSES3 x #

to :: Rep SSES3 x -> SSES3 #

Hashable SSES3 Source # 

Methods

hashWithSalt :: Int -> SSES3 -> Int #

hash :: SSES3 -> Int #

NFData SSES3 Source # 

Methods

rnf :: SSES3 -> () #

FromXML SSES3 Source # 

Methods

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

ToXML SSES3 Source # 

Methods

toXML :: SSES3 -> XML #

type Rep SSES3 Source # 
type Rep SSES3 = D1 * (MetaData "SSES3" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" False) (C1 * (MetaCons "SSES3'" PrefixI False) (U1 *))

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 # 
Data SelectObjectContentEventStream Source # 

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 # 
Show SelectObjectContentEventStream Source # 
Generic SelectObjectContentEventStream Source # 
Hashable SelectObjectContentEventStream Source # 
NFData SelectObjectContentEventStream Source # 
FromXML SelectObjectContentEventStream Source # 
type Rep SelectObjectContentEventStream Source # 
type Rep SelectObjectContentEventStream = D1 * (MetaData "SelectObjectContentEventStream" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" False) (C1 * (MetaCons "SelectObjectContentEventStream'" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_socesProgress") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe ProgressEvent))) (S1 * (MetaSel (Just Symbol "_socesRecords") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe RecordsEvent)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_socesCont") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe ContinuationEvent))) ((:*:) * (S1 * (MetaSel (Just Symbol "_socesStats") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe StatsEvent))) (S1 * (MetaSel (Just Symbol "_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 # 
Data SelectParameters Source # 

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 # 
Show SelectParameters Source # 
Generic SelectParameters Source # 
Hashable SelectParameters Source # 
NFData SelectParameters Source # 

Methods

rnf :: SelectParameters -> () #

ToXML SelectParameters Source # 
type Rep SelectParameters Source # 
type Rep SelectParameters = D1 * (MetaData "SelectParameters" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" False) (C1 * (MetaCons "SelectParameters'" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_spInputSerialization") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * InputSerialization)) (S1 * (MetaSel (Just Symbol "_spExpressionType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * ExpressionType))) ((:*:) * (S1 * (MetaSel (Just Symbol "_spExpression") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text)) (S1 * (MetaSel (Just Symbol "_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 # 
Data ServerSideEncryptionByDefault Source # 

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 # 
Generic ServerSideEncryptionByDefault Source # 
Hashable ServerSideEncryptionByDefault Source # 
NFData ServerSideEncryptionByDefault Source # 
FromXML ServerSideEncryptionByDefault Source # 
ToXML ServerSideEncryptionByDefault Source # 
type Rep ServerSideEncryptionByDefault Source # 
type Rep ServerSideEncryptionByDefault = D1 * (MetaData "ServerSideEncryptionByDefault" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" False) (C1 * (MetaCons "ServerSideEncryptionByDefault'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_ssebdKMSMasterKeyId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe (Sensitive Text)))) (S1 * (MetaSel (Just Symbol "_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 # 
Data ServerSideEncryptionConfiguration Source # 

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 # 
Generic ServerSideEncryptionConfiguration Source # 
Hashable ServerSideEncryptionConfiguration Source # 
NFData ServerSideEncryptionConfiguration Source # 
FromXML ServerSideEncryptionConfiguration Source # 
ToXML ServerSideEncryptionConfiguration Source # 
type Rep ServerSideEncryptionConfiguration Source # 
type Rep ServerSideEncryptionConfiguration = D1 * (MetaData "ServerSideEncryptionConfiguration" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" True) (C1 * (MetaCons "ServerSideEncryptionConfiguration'" PrefixI True) (S1 * (MetaSel (Just Symbol "_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 # 
Data ServerSideEncryptionRule Source # 

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 # 
Generic ServerSideEncryptionRule Source # 
Hashable ServerSideEncryptionRule Source # 
NFData ServerSideEncryptionRule Source # 
FromXML ServerSideEncryptionRule Source # 
ToXML ServerSideEncryptionRule Source # 
type Rep ServerSideEncryptionRule Source # 
type Rep ServerSideEncryptionRule = D1 * (MetaData "ServerSideEncryptionRule" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" True) (C1 * (MetaCons "ServerSideEncryptionRule'" PrefixI True) (S1 * (MetaSel (Just Symbol "_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 # 
Data SourceSelectionCriteria Source # 

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 # 
Show SourceSelectionCriteria Source # 
Generic SourceSelectionCriteria Source # 
Hashable SourceSelectionCriteria Source # 
NFData SourceSelectionCriteria Source # 

Methods

rnf :: SourceSelectionCriteria -> () #

FromXML SourceSelectionCriteria Source # 
ToXML SourceSelectionCriteria Source # 
type Rep SourceSelectionCriteria Source # 
type Rep SourceSelectionCriteria = D1 * (MetaData "SourceSelectionCriteria" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" True) (C1 * (MetaCons "SourceSelectionCriteria'" PrefixI True) (S1 * (MetaSel (Just Symbol "_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 # 
Data SseKMSEncryptedObjects Source # 

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 # 
Show SseKMSEncryptedObjects Source # 
Generic SseKMSEncryptedObjects Source # 
Hashable SseKMSEncryptedObjects Source # 
NFData SseKMSEncryptedObjects Source # 

Methods

rnf :: SseKMSEncryptedObjects -> () #

FromXML SseKMSEncryptedObjects Source # 
ToXML SseKMSEncryptedObjects Source # 
type Rep SseKMSEncryptedObjects Source # 
type Rep SseKMSEncryptedObjects = D1 * (MetaData "SseKMSEncryptedObjects" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" True) (C1 * (MetaCons "SseKMSEncryptedObjects'" PrefixI True) (S1 * (MetaSel (Just Symbol "_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 # 

Methods

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

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

Data Stats Source # 

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 # 
Show Stats Source # 

Methods

showsPrec :: Int -> Stats -> ShowS #

show :: Stats -> String #

showList :: [Stats] -> ShowS #

Generic Stats Source # 

Associated Types

type Rep Stats :: * -> * #

Methods

from :: Stats -> Rep Stats x #

to :: Rep Stats x -> Stats #

Hashable Stats Source # 

Methods

hashWithSalt :: Int -> Stats -> Int #

hash :: Stats -> Int #

NFData Stats Source # 

Methods

rnf :: Stats -> () #

FromXML Stats Source # 

Methods

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

type Rep Stats Source # 
type Rep Stats = D1 * (MetaData "Stats" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" False) (C1 * (MetaCons "Stats'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_sBytesReturned") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Integer))) ((:*:) * (S1 * (MetaSel (Just Symbol "_sBytesScanned") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Integer))) (S1 * (MetaSel (Just Symbol "_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 # 
Data StatsEvent Source # 

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 # 
Show StatsEvent Source # 
Generic StatsEvent Source # 

Associated Types

type Rep StatsEvent :: * -> * #

Hashable StatsEvent Source # 
NFData StatsEvent Source # 

Methods

rnf :: StatsEvent -> () #

FromXML StatsEvent Source # 
type Rep StatsEvent Source # 
type Rep StatsEvent = D1 * (MetaData "StatsEvent" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" True) (C1 * (MetaCons "StatsEvent'" PrefixI True) (S1 * (MetaSel (Just Symbol "_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 # 
Data StorageClassAnalysis Source # 

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 # 
Show StorageClassAnalysis Source # 
Generic StorageClassAnalysis Source # 
Hashable StorageClassAnalysis Source # 
NFData StorageClassAnalysis Source # 

Methods

rnf :: StorageClassAnalysis -> () #

FromXML StorageClassAnalysis Source # 
ToXML StorageClassAnalysis Source # 
type Rep StorageClassAnalysis Source # 
type Rep StorageClassAnalysis = D1 * (MetaData "StorageClassAnalysis" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" True) (C1 * (MetaCons "StorageClassAnalysis'" PrefixI True) (S1 * (MetaSel (Just Symbol "_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 # 
Data StorageClassAnalysisDataExport Source # 

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 # 
Show StorageClassAnalysisDataExport Source # 
Generic StorageClassAnalysisDataExport Source # 
Hashable StorageClassAnalysisDataExport Source # 
NFData StorageClassAnalysisDataExport Source # 
FromXML StorageClassAnalysisDataExport Source # 
ToXML StorageClassAnalysisDataExport Source # 
type Rep StorageClassAnalysisDataExport Source # 
type Rep StorageClassAnalysisDataExport = D1 * (MetaData "StorageClassAnalysisDataExport" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" False) (C1 * (MetaCons "StorageClassAnalysisDataExport'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_scadeOutputSchemaVersion") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * StorageClassAnalysisSchemaVersion)) (S1 * (MetaSel (Just Symbol "_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 # 

Methods

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

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

Data Tag Source # 

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 # 
Show Tag Source # 

Methods

showsPrec :: Int -> Tag -> ShowS #

show :: Tag -> String #

showList :: [Tag] -> ShowS #

Generic Tag Source # 

Associated Types

type Rep Tag :: * -> * #

Methods

from :: Tag -> Rep Tag x #

to :: Rep Tag x -> Tag #

Hashable Tag Source # 

Methods

hashWithSalt :: Int -> Tag -> Int #

hash :: Tag -> Int #

NFData Tag Source # 

Methods

rnf :: Tag -> () #

FromXML Tag Source # 

Methods

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

ToXML Tag Source # 

Methods

toXML :: Tag -> XML #

type Rep Tag Source # 
type Rep Tag = D1 * (MetaData "Tag" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" False) (C1 * (MetaCons "Tag'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_tagKey") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * ObjectKey)) (S1 * (MetaSel (Just Symbol "_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 # 

Methods

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

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

Data Tagging Source # 

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 # 
Show Tagging Source # 
Generic Tagging Source # 

Associated Types

type Rep Tagging :: * -> * #

Methods

from :: Tagging -> Rep Tagging x #

to :: Rep Tagging x -> Tagging #

Hashable Tagging Source # 

Methods

hashWithSalt :: Int -> Tagging -> Int #

hash :: Tagging -> Int #

NFData Tagging Source # 

Methods

rnf :: Tagging -> () #

ToXML Tagging Source # 

Methods

toXML :: Tagging -> XML #

type Rep Tagging Source # 
type Rep Tagging = D1 * (MetaData "Tagging" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" True) (C1 * (MetaCons "Tagging'" PrefixI True) (S1 * (MetaSel (Just Symbol "_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 # 
Data TargetGrant Source # 

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 # 
Show TargetGrant Source # 
Generic TargetGrant Source # 

Associated Types

type Rep TargetGrant :: * -> * #

Hashable TargetGrant Source # 
NFData TargetGrant Source # 

Methods

rnf :: TargetGrant -> () #

FromXML TargetGrant Source # 
ToXML TargetGrant Source # 

Methods

toXML :: TargetGrant -> XML #

type Rep TargetGrant Source # 
type Rep TargetGrant = D1 * (MetaData "TargetGrant" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" False) (C1 * (MetaCons "TargetGrant'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_tgPermission") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe BucketLogsPermission))) (S1 * (MetaSel (Just Symbol "_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 # 
Data TopicConfiguration Source # 

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 # 
Show TopicConfiguration Source # 
Generic TopicConfiguration Source # 
Hashable TopicConfiguration Source # 
NFData TopicConfiguration Source # 

Methods

rnf :: TopicConfiguration -> () #

FromXML TopicConfiguration Source # 
ToXML TopicConfiguration Source # 
type Rep TopicConfiguration Source # 
type Rep TopicConfiguration = D1 * (MetaData "TopicConfiguration" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" False) (C1 * (MetaCons "TopicConfiguration'" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_tcId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_tcFilter") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe NotificationConfigurationFilter)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_tcTopicARN") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text)) (S1 * (MetaSel (Just Symbol "_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 # 
Data Transition Source # 

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 # 
Show Transition Source # 
Generic Transition Source # 

Associated Types

type Rep Transition :: * -> * #

Hashable Transition Source # 
NFData Transition Source # 

Methods

rnf :: Transition -> () #

FromXML Transition Source # 
ToXML Transition Source # 

Methods

toXML :: Transition -> XML #

type Rep Transition Source # 
type Rep Transition = D1 * (MetaData "Transition" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" False) (C1 * (MetaCons "Transition'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_tDays") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Int))) ((:*:) * (S1 * (MetaSel (Just Symbol "_tDate") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe RFC822))) (S1 * (MetaSel (Just Symbol "_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 # 
Data VersioningConfiguration Source # 

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 # 
Show VersioningConfiguration Source # 
Generic VersioningConfiguration Source # 
Hashable VersioningConfiguration Source # 
NFData VersioningConfiguration Source # 

Methods

rnf :: VersioningConfiguration -> () #

ToXML VersioningConfiguration Source # 
type Rep VersioningConfiguration Source # 
type Rep VersioningConfiguration = D1 * (MetaData "VersioningConfiguration" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" False) (C1 * (MetaCons "VersioningConfiguration'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_vcStatus") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe BucketVersioningStatus))) (S1 * (MetaSel (Just Symbol "_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 # 
Data WebsiteConfiguration Source # 

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 # 
Show WebsiteConfiguration Source # 
Generic WebsiteConfiguration Source # 
Hashable WebsiteConfiguration Source # 
NFData WebsiteConfiguration Source # 

Methods

rnf :: WebsiteConfiguration -> () #

ToXML WebsiteConfiguration Source # 
type Rep WebsiteConfiguration Source # 
type Rep WebsiteConfiguration = D1 * (MetaData "WebsiteConfiguration" "Network.AWS.S3.Types.Product" "amazonka-s3-1.6.0-AdElsico9UIGqHgrDvALBR" False) (C1 * (MetaCons "WebsiteConfiguration'" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_wcRedirectAllRequestsTo") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe RedirectAllRequestsTo))) (S1 * (MetaSel (Just Symbol "_wcErrorDocument") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe ErrorDocument)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_wcIndexDocument") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe IndexDocument))) (S1 * (MetaSel (Just Symbol "_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: