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

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

Network.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 sum of available AWS regions.

Constructors

Ireland

Europe / eu-west-1

Frankfurt

Europe / eu-central-1

Tokyo

Asia Pacific / ap-northeast-1

Singapore

Asia Pacific / ap-southeast-1

Sydney

Asia Pacific / ap-southeast-2

Bombay

Asia Pacific / ap-south-1

Beijing

China / cn-north-1

NorthVirginia

US / us-east-1

NorthCalifornia

US / us-west-1

Oregon

US / us-west-2

GovCloud

AWS GovCloud / us-gov-west-1

GovCloudFIPS

AWS GovCloud (FIPS 140-2) S3 Only / fips-us-gov-west-1

SaoPaulo

South America / sa-east-1

Instances

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 #

NFData Region 

Methods

rnf :: Region -> () #

ToLog Region 

Methods

build :: Region -> Builder #

FromXML Region 

Methods

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

ToXML Region 

Methods

toXML :: Region -> XML #

ToByteString Region 

Methods

toBS :: Region -> ByteString #

FromJSON Region 

Methods

parseJSON :: Value -> Parser Region #

ToJSON Region 

Methods

toJSON :: Region -> Value #

toEncoding :: Region -> Encoding #

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.4.4-37acnMZBU148gTrDuH4Pfk" False) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "Ireland" PrefixI False) U1) ((:+:) (C1 (MetaCons "Frankfurt" PrefixI False) U1) (C1 (MetaCons "Tokyo" PrefixI False) U1))) ((:+:) (C1 (MetaCons "Singapore" PrefixI False) U1) ((:+:) (C1 (MetaCons "Sydney" PrefixI False) U1) (C1 (MetaCons "Bombay" PrefixI False) U1)))) ((:+:) ((:+:) (C1 (MetaCons "Beijing" PrefixI False) U1) ((:+:) (C1 (MetaCons "NorthVirginia" PrefixI False) U1) (C1 (MetaCons "NorthCalifornia" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "Oregon" PrefixI False) U1) (C1 (MetaCons "GovCloud" PrefixI False) U1)) ((:+:) (C1 (MetaCons "GovCloudFIPS" PrefixI False) U1) (C1 (MetaCons "SaoPaulo" 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 # 
NFData BucketName Source # 

Methods

rnf :: BucketName -> () #

ToLog BucketName Source # 

Methods

build :: BucketName -> Builder #

FromXML BucketName Source # 

Methods

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

ToXML BucketName Source # 

Methods

toXML :: BucketName -> XML #

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

Methods

parser :: Parser BucketName #

ToText BucketName Source # 

Methods

toText :: BucketName -> Text #

type Rep BucketName Source # 
type Rep BucketName = D1 (MetaData "BucketName" "Network.AWS.S3.Internal" "amazonka-s3-1.4.4-HefXwCotGB7GxFwqy8ThdO" 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 -> () #

ToLog ETag Source # 

Methods

build :: ETag -> Builder #

FromXML ETag Source # 

Methods

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

ToXML ETag Source # 

Methods

toXML :: ETag -> XML #

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.4.4-HefXwCotGB7GxFwqy8ThdO" 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 -> () #

ToLog ObjectVersionId Source # 
FromXML ObjectVersionId Source # 

Methods

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

ToXML ObjectVersionId Source # 

Methods

toXML :: ObjectVersionId -> XML #

ToQuery ObjectVersionId Source # 
ToByteString ObjectVersionId Source # 
FromText ObjectVersionId Source # 

Methods

parser :: Parser ObjectVersionId #

ToText ObjectVersionId Source # 
type Rep ObjectVersionId Source # 
type Rep ObjectVersionId = D1 (MetaData "ObjectVersionId" "Network.AWS.S3.Internal" "amazonka-s3-1.4.4-HefXwCotGB7GxFwqy8ThdO" 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 -> () #

ToLog LocationConstraint Source # 
FromXML LocationConstraint Source # 
ToXML LocationConstraint Source # 
ToByteString LocationConstraint Source # 
FromText LocationConstraint Source # 

Methods

parser :: Parser LocationConstraint #

ToText LocationConstraint Source # 
type Rep LocationConstraint Source # 
type Rep LocationConstraint = D1 (MetaData "LocationConstraint" "Network.AWS.S3.Internal" "amazonka-s3-1.4.4-HefXwCotGB7GxFwqy8ThdO" 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 -> () #

ToLog ObjectKey Source # 

Methods

build :: ObjectKey -> Builder #

ToPath ObjectKey Source # 
FromXML ObjectKey Source # 

Methods

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

ToXML ObjectKey Source # 

Methods

toXML :: ObjectKey -> XML #

ToQuery ObjectKey Source # 
ToByteString ObjectKey Source # 

Methods

toBS :: ObjectKey -> ByteString #

FromText ObjectKey Source # 

Methods

parser :: Parser ObjectKey #

ToText ObjectKey Source # 

Methods

toText :: ObjectKey -> Text #

type Rep ObjectKey Source # 
type Rep ObjectKey = D1 (MetaData "ObjectKey" "Network.AWS.S3.Internal" "amazonka-s3-1.4.4-HefXwCotGB7GxFwqy8ThdO" 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.

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 -> () #

ToHeader BucketAccelerateStatus Source # 
FromXML BucketAccelerateStatus Source # 
ToXML 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.4.4-HefXwCotGB7GxFwqy8ThdO" 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 -> () #

ToHeader BucketCannedACL Source # 
ToXML BucketCannedACL Source # 

Methods

toXML :: BucketCannedACL -> XML #

ToQuery BucketCannedACL Source # 
ToByteString BucketCannedACL Source # 
FromText BucketCannedACL Source # 

Methods

parser :: Parser BucketCannedACL #

ToText BucketCannedACL Source # 
type Rep BucketCannedACL Source # 
type Rep BucketCannedACL = D1 (MetaData "BucketCannedACL" "Network.AWS.S3.Types.Sum" "amazonka-s3-1.4.4-HefXwCotGB7GxFwqy8ThdO" 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 -> () #

ToHeader BucketLogsPermission Source # 
FromXML BucketLogsPermission Source # 
ToXML BucketLogsPermission Source # 
ToQuery BucketLogsPermission Source # 
ToByteString BucketLogsPermission Source # 
FromText BucketLogsPermission Source # 

Methods

parser :: Parser BucketLogsPermission #

ToText BucketLogsPermission Source # 
type Rep BucketLogsPermission Source # 
type Rep BucketLogsPermission = D1 (MetaData "BucketLogsPermission" "Network.AWS.S3.Types.Sum" "amazonka-s3-1.4.4-HefXwCotGB7GxFwqy8ThdO" 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 -> () #

ToHeader BucketVersioningStatus Source # 
FromXML BucketVersioningStatus Source # 
ToXML 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.4.4-HefXwCotGB7GxFwqy8ThdO" False) ((:+:) (C1 (MetaCons "BVSEnabled" PrefixI False) U1) (C1 (MetaCons "BVSSuspended" 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 -> () #

ToHeader EncodingType Source # 
FromXML EncodingType Source # 

Methods

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

ToXML EncodingType Source # 

Methods

toXML :: EncodingType -> XML #

ToQuery EncodingType Source # 
ToByteString EncodingType Source # 
FromText EncodingType Source # 

Methods

parser :: Parser EncodingType #

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.4.4-HefXwCotGB7GxFwqy8ThdO" 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 -> () #

ToHeader Event Source # 

Methods

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

FromXML Event Source # 

Methods

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

ToXML Event Source # 

Methods

toXML :: Event -> XML #

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.4.4-HefXwCotGB7GxFwqy8ThdO" 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 -> () #

ToHeader ExpirationStatus Source # 
FromXML ExpirationStatus Source # 
ToXML ExpirationStatus Source # 
ToQuery ExpirationStatus Source # 
ToByteString ExpirationStatus Source # 
FromText ExpirationStatus Source # 

Methods

parser :: Parser ExpirationStatus #

ToText ExpirationStatus Source # 
type Rep ExpirationStatus Source # 
type Rep ExpirationStatus = D1 (MetaData "ExpirationStatus" "Network.AWS.S3.Types.Sum" "amazonka-s3-1.4.4-HefXwCotGB7GxFwqy8ThdO" False) ((:+:) (C1 (MetaCons "ESDisabled" PrefixI False) U1) (C1 (MetaCons "ESEnabled" 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 -> () #

ToHeader FilterRuleName Source # 
FromXML FilterRuleName Source # 

Methods

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

ToXML FilterRuleName Source # 

Methods

toXML :: FilterRuleName -> XML #

ToQuery FilterRuleName Source # 
ToByteString FilterRuleName Source # 
FromText FilterRuleName Source # 

Methods

parser :: Parser FilterRuleName #

ToText FilterRuleName Source # 
type Rep FilterRuleName Source # 
type Rep FilterRuleName = D1 (MetaData "FilterRuleName" "Network.AWS.S3.Types.Sum" "amazonka-s3-1.4.4-HefXwCotGB7GxFwqy8ThdO" False) ((:+:) (C1 (MetaCons "Prefix" PrefixI False) U1) (C1 (MetaCons "Suffix" 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 -> () #

ToHeader MFADelete Source # 
ToXML MFADelete Source # 

Methods

toXML :: MFADelete -> XML #

ToQuery MFADelete Source # 
ToByteString MFADelete Source # 

Methods

toBS :: MFADelete -> ByteString #

FromText MFADelete Source # 

Methods

parser :: Parser MFADelete #

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.4.4-HefXwCotGB7GxFwqy8ThdO" 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 -> () #

ToHeader MFADeleteStatus Source # 
FromXML MFADeleteStatus Source # 

Methods

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

ToQuery MFADeleteStatus Source # 
ToByteString MFADeleteStatus Source # 
FromText MFADeleteStatus Source # 

Methods

parser :: Parser MFADeleteStatus #

ToText MFADeleteStatus Source # 
type Rep MFADeleteStatus Source # 
type Rep MFADeleteStatus = D1 (MetaData "MFADeleteStatus" "Network.AWS.S3.Types.Sum" "amazonka-s3-1.4.4-HefXwCotGB7GxFwqy8ThdO" False) ((:+:) (C1 (MetaCons "MDSDisabled" PrefixI False) U1) (C1 (MetaCons "MDSEnabled" PrefixI False) U1))

MetadataDirective

data MetadataDirective Source #

Constructors

Copy 
Replace 

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 -> () #

ToHeader MetadataDirective Source # 
ToXML MetadataDirective Source # 
ToQuery MetadataDirective Source # 
ToByteString MetadataDirective Source # 
FromText MetadataDirective Source # 

Methods

parser :: Parser MetadataDirective #

ToText MetadataDirective Source # 
type Rep MetadataDirective Source # 
type Rep MetadataDirective = D1 (MetaData "MetadataDirective" "Network.AWS.S3.Types.Sum" "amazonka-s3-1.4.4-HefXwCotGB7GxFwqy8ThdO" False) ((:+:) (C1 (MetaCons "Copy" PrefixI False) U1) (C1 (MetaCons "Replace" 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 -> () #

ToHeader ObjectCannedACL Source # 
ToXML ObjectCannedACL Source # 

Methods

toXML :: ObjectCannedACL -> XML #

ToQuery ObjectCannedACL Source # 
ToByteString ObjectCannedACL Source # 
FromText ObjectCannedACL Source # 

Methods

parser :: Parser ObjectCannedACL #

ToText ObjectCannedACL Source # 
type Rep ObjectCannedACL Source # 
type Rep ObjectCannedACL = D1 (MetaData "ObjectCannedACL" "Network.AWS.S3.Types.Sum" "amazonka-s3-1.4.4-HefXwCotGB7GxFwqy8ThdO" 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 -> () #

ToHeader ObjectStorageClass Source # 
FromXML ObjectStorageClass Source # 
ToQuery ObjectStorageClass Source # 
ToByteString ObjectStorageClass Source # 
FromText ObjectStorageClass Source # 

Methods

parser :: Parser ObjectStorageClass #

ToText ObjectStorageClass Source # 
type Rep ObjectStorageClass Source # 
type Rep ObjectStorageClass = D1 (MetaData "ObjectStorageClass" "Network.AWS.S3.Types.Sum" "amazonka-s3-1.4.4-HefXwCotGB7GxFwqy8ThdO" 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 # 
ToHeader ObjectVersionStorageClass Source # 
FromXML 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.4.4-HefXwCotGB7GxFwqy8ThdO" False) (C1 (MetaCons "OVSCStandard" 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 -> () #

ToHeader Payer Source # 

Methods

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

FromXML Payer Source # 

Methods

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

ToXML Payer Source # 

Methods

toXML :: Payer -> XML #

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.4.4-HefXwCotGB7GxFwqy8ThdO" 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 -> () #

ToHeader Permission Source # 
FromXML Permission Source # 

Methods

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

ToXML Permission Source # 

Methods

toXML :: Permission -> XML #

ToQuery Permission Source # 
ToByteString Permission Source # 
FromText Permission Source # 

Methods

parser :: Parser Permission #

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.4.4-HefXwCotGB7GxFwqy8ThdO" 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 -> () #

ToHeader Protocol Source # 

Methods

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

FromXML Protocol Source # 

Methods

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

ToXML Protocol Source # 

Methods

toXML :: Protocol -> XML #

ToQuery Protocol Source # 
ToByteString Protocol Source # 

Methods

toBS :: Protocol -> ByteString #

FromText Protocol Source # 

Methods

parser :: Parser Protocol #

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.4.4-HefXwCotGB7GxFwqy8ThdO" False) ((:+:) (C1 (MetaCons "HTTP" PrefixI False) U1) (C1 (MetaCons "HTTPS" 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 -> () #

ToHeader ReplicationRuleStatus Source # 
FromXML ReplicationRuleStatus Source # 
ToXML ReplicationRuleStatus Source # 
ToQuery ReplicationRuleStatus Source # 
ToByteString ReplicationRuleStatus Source # 
FromText ReplicationRuleStatus Source # 

Methods

parser :: Parser ReplicationRuleStatus #

ToText ReplicationRuleStatus Source # 
type Rep ReplicationRuleStatus Source # 
type Rep ReplicationRuleStatus = D1 (MetaData "ReplicationRuleStatus" "Network.AWS.S3.Types.Sum" "amazonka-s3-1.4.4-HefXwCotGB7GxFwqy8ThdO" False) ((:+:) (C1 (MetaCons "Disabled" PrefixI False) U1) (C1 (MetaCons "Enabled" PrefixI False) U1))

ReplicationStatus

data ReplicationStatus Source #

Constructors

Complete 
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 -> () #

ToHeader ReplicationStatus Source # 
FromXML ReplicationStatus Source # 
ToQuery ReplicationStatus Source # 
ToByteString ReplicationStatus Source # 
FromText ReplicationStatus Source # 

Methods

parser :: Parser ReplicationStatus #

ToText ReplicationStatus Source # 
type Rep ReplicationStatus Source # 
type Rep ReplicationStatus = D1 (MetaData "ReplicationStatus" "Network.AWS.S3.Types.Sum" "amazonka-s3-1.4.4-HefXwCotGB7GxFwqy8ThdO" False) ((:+:) ((:+:) (C1 (MetaCons "Complete" 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 -> () #

ToHeader RequestCharged Source # 
FromXML RequestCharged Source # 

Methods

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

ToQuery RequestCharged Source # 
ToByteString RequestCharged Source # 
FromText RequestCharged Source # 

Methods

parser :: Parser RequestCharged #

ToText RequestCharged Source # 
type Rep RequestCharged Source # 
type Rep RequestCharged = D1 (MetaData "RequestCharged" "Network.AWS.S3.Types.Sum" "amazonka-s3-1.4.4-HefXwCotGB7GxFwqy8ThdO" 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 -> () #

ToHeader RequestPayer Source # 
ToXML RequestPayer Source # 

Methods

toXML :: RequestPayer -> XML #

ToQuery RequestPayer Source # 
ToByteString RequestPayer Source # 
FromText RequestPayer Source # 

Methods

parser :: Parser RequestPayer #

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.4.4-HefXwCotGB7GxFwqy8ThdO" False) (C1 (MetaCons "RPRequester" 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 -> () #

ToHeader ServerSideEncryption Source # 
FromXML ServerSideEncryption Source # 
ToXML ServerSideEncryption Source # 
ToQuery ServerSideEncryption Source # 
ToByteString ServerSideEncryption Source # 
FromText ServerSideEncryption Source # 

Methods

parser :: Parser ServerSideEncryption #

ToText ServerSideEncryption Source # 
type Rep ServerSideEncryption Source # 
type Rep ServerSideEncryption = D1 (MetaData "ServerSideEncryption" "Network.AWS.S3.Types.Sum" "amazonka-s3-1.4.4-HefXwCotGB7GxFwqy8ThdO" False) ((:+:) (C1 (MetaCons "AES256" PrefixI False) U1) (C1 (MetaCons "AWSKMS" 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 -> () #

ToHeader StorageClass Source # 
FromXML StorageClass Source # 

Methods

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

ToXML StorageClass Source # 

Methods

toXML :: StorageClass -> XML #

ToQuery StorageClass Source # 
ToByteString StorageClass Source # 
FromText StorageClass Source # 

Methods

parser :: Parser StorageClass #

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.4.4-HefXwCotGB7GxFwqy8ThdO" False) ((:+:) (C1 (MetaCons "ReducedRedundancy" PrefixI False) U1) ((:+:) (C1 (MetaCons "Standard" PrefixI False) U1) (C1 (MetaCons "StandardIA" PrefixI False) U1)))

TransitionStorageClass

data TransitionStorageClass Source #

Constructors

TSCGlacier 
TSCStandardIA 

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 -> () #

ToHeader TransitionStorageClass Source # 
FromXML TransitionStorageClass Source # 
ToXML 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.4.4-HefXwCotGB7GxFwqy8ThdO" False) ((:+:) (C1 (MetaCons "TSCGlacier" 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 -> () #

ToHeader Type Source # 

Methods

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

FromXML Type Source # 

Methods

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

ToXML Type Source # 

Methods

toXML :: Type -> XML #

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.4.4-HefXwCotGB7GxFwqy8ThdO" 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.4.4-HefXwCotGB7GxFwqy8ThdO" 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 :: 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.4.4-HefXwCotGB7GxFwqy8ThdO" 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 :: 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.4.4-HefXwCotGB7GxFwqy8ThdO" 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:

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 # 

Methods

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

type Rep Bucket Source # 
type Rep Bucket = D1 (MetaData "Bucket" "Network.AWS.S3.Types.Product" "amazonka-s3-1.4.4-HefXwCotGB7GxFwqy8ThdO" False) (C1 (MetaCons "Bucket'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_bCreationDate") NoSourceUnpackedness SourceStrict DecidedUnpack) (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.4.4-HefXwCotGB7GxFwqy8ThdO" 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.4.4-HefXwCotGB7GxFwqy8ThdO" 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.4.4-HefXwCotGB7GxFwqy8ThdO" 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 # 

Methods

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

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.4.4-HefXwCotGB7GxFwqy8ThdO" 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 :: 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.

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 # 

Methods

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

type Rep CommonPrefix Source # 
type Rep CommonPrefix = D1 (MetaData "CommonPrefix" "Network.AWS.S3.Types.Product" "amazonka-s3-1.4.4-HefXwCotGB7GxFwqy8ThdO" 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.4.4-HefXwCotGB7GxFwqy8ThdO" 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.4.4-HefXwCotGB7GxFwqy8ThdO" False) (C1 (MetaCons "CompletedPart'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_cpPartNumber") NoSourceUnpackedness SourceStrict DecidedUnpack) (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 :: 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 # 

Methods

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

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.4.4-HefXwCotGB7GxFwqy8ThdO" 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 :: 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.

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.4.4-HefXwCotGB7GxFwqy8ThdO" 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 # 

Methods

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

type Rep CopyPartResult Source # 
type Rep CopyPartResult = D1 (MetaData "CopyPartResult" "Network.AWS.S3.Types.Product" "amazonka-s3-1.4.4-HefXwCotGB7GxFwqy8ThdO" 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.4.4-HefXwCotGB7GxFwqy8ThdO" 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 :: 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.4.4-HefXwCotGB7GxFwqy8ThdO" 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 :: 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.4.4-HefXwCotGB7GxFwqy8ThdO" 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 # 

Methods

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

type Rep DeletedObject Source # 
type Rep DeletedObject = D1 (MetaData "DeletedObject" "Network.AWS.S3.Types.Product" "amazonka-s3-1.4.4-HefXwCotGB7GxFwqy8ThdO" 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 #

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 # 

Methods

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

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.4.4-HefXwCotGB7GxFwqy8ThdO" False) (C1 (MetaCons "Destination'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_dStorageClass") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe StorageClass))) (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:

dStorageClass :: Lens' Destination (Maybe StorageClass) Source #

The class of storage used to store the object.

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.

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 # 

Methods

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

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.4.4-HefXwCotGB7GxFwqy8ThdO" 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 :: 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 # 

Methods

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

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.4.4-HefXwCotGB7GxFwqy8ThdO" 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.

frName :: Lens' FilterRule (Maybe FilterRuleName) Source #

Object key name prefix or suffix identifying one or more objects to which the filtering rule applies. Maximum prefix length can be up to 1,024 characters. Overlapping prefixes and suffixes are not supported. For more information, go to Configuring Event Notifications in the Amazon Simple Storage Service Developer Guide.

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.4.4-HefXwCotGB7GxFwqy8ThdO" 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 # 

Methods

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

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 :: 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 # 

Methods

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

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.4.4-HefXwCotGB7GxFwqy8ThdO" 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 :: 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 samplebucket/images/ 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 # 

Methods

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

type Rep Initiator Source # 
type Rep Initiator = D1 (MetaData "Initiator" "Network.AWS.S3.Types.Product" "amazonka-s3-1.4.4-HefXwCotGB7GxFwqy8ThdO" 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 :: 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.

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.4.4-HefXwCotGB7GxFwqy8ThdO" 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.4.4-HefXwCotGB7GxFwqy8ThdO" 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 :: 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 # 

Methods

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

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:

lrId :: Lens' LifecycleRule (Maybe Text) Source #

Unique identifier for the rule. The value cannot be longer than 255 characters.

lrPrefix :: Lens' LifecycleRule Text Source #

Prefix identifying one or more objects to which the rule applies.

lrStatus :: Lens' LifecycleRule ExpirationStatus Source #

If 'Enabled', the rule is currently being applied. If 'Disabled', the rule is not currently being applied.

LoggingEnabled

data LoggingEnabled Source #

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 # 

Methods

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

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.4.4-HefXwCotGB7GxFwqy8ThdO" False) (C1 (MetaCons "LoggingEnabled'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_leTargetBucket") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_leTargetGrants") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [TargetGrant]))) (S1 (MetaSel (Just Symbol "_leTargetPrefix") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))))

loggingEnabled :: 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:

leTargetBucket :: Lens' LoggingEnabled (Maybe 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 (Maybe Text) Source #

This element lets you specify a prefix for the keys that the log files will be stored under.

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 # 

Methods

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

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 :: 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.4.4-HefXwCotGB7GxFwqy8ThdO" 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:

nveNoncurrentDays :: Lens' NoncurrentVersionExpiration Int Source #

Specifies the number of days an object is noncurrent before Amazon S3 can perform the associated action. For information about the noncurrent days calculations, see How Amazon S3 Calculates When an Object Became Noncurrent in the Amazon Simple Storage Service Developer Guide.

NoncurrentVersionTransition

data NoncurrentVersionTransition Source #

Container for the transition rule that describes when noncurrent objects transition to the STANDARD_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 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.4.4-HefXwCotGB7GxFwqy8ThdO" False) (C1 (MetaCons "NoncurrentVersionTransition'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_nvtNoncurrentDays") NoSourceUnpackedness SourceStrict DecidedUnpack) (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:

nvtNoncurrentDays :: Lens' NoncurrentVersionTransition Int Source #

Specifies the number of days an object is noncurrent before Amazon S3 can perform the associated action. For information about the noncurrent days calculations, see How Amazon S3 Calculates When an Object Became Noncurrent in the Amazon Simple Storage Service Developer Guide.

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.4.4-HefXwCotGB7GxFwqy8ThdO" 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 #

Container for object key name filtering rules. For information about key name filtering, go to Configuring Event Notifications in the Amazon Simple Storage Service Developer Guide.

See: notificationConfigurationFilter smart constructor.

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.4.4-HefXwCotGB7GxFwqy8ThdO" 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 # 

Methods

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

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.4.4-HefXwCotGB7GxFwqy8ThdO" 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 :: 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 # 

Methods

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

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 :: 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.

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.4.4-HefXwCotGB7GxFwqy8ThdO" 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.4.4-HefXwCotGB7GxFwqy8ThdO" 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 :: 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.

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.4.4-HefXwCotGB7GxFwqy8ThdO" 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 :: 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.

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 # 

Methods

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

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.4.4-HefXwCotGB7GxFwqy8ThdO" 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 :: 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.4.4-HefXwCotGB7GxFwqy8ThdO" 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 :: 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.4.4-HefXwCotGB7GxFwqy8ThdO" 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 :: 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 #

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 # 

Methods

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

ToXML ReplicationRule Source # 

Methods

toXML :: ReplicationRule -> XML #

type Rep ReplicationRule Source # 
type Rep ReplicationRule = D1 (MetaData "ReplicationRule" "Network.AWS.S3.Types.Product" "amazonka-s3-1.4.4-HefXwCotGB7GxFwqy8ThdO" False) (C1 (MetaCons "ReplicationRule'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_rrId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_rrPrefix") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text))) ((:*:) (S1 (MetaSel (Just Symbol "_rrStatus") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 ReplicationRuleStatus)) (S1 (MetaSel (Just Symbol "_rrDestination") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Destination)))))

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 :: Lens' ReplicationRule (Maybe Text) Source #

Unique identifier for the rule. The value cannot be longer than 255 characters.

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.

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.4.4-HefXwCotGB7GxFwqy8ThdO" 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 :: Lens' RequestPaymentConfiguration Payer Source #

Specifies who pays for the download and request fees.

RestoreRequest

data RestoreRequest Source #

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 #

Read RestoreRequest Source # 
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 # 
type Rep RestoreRequest = D1 (MetaData "RestoreRequest" "Network.AWS.S3.Types.Product" "amazonka-s3-1.4.4-HefXwCotGB7GxFwqy8ThdO" True) (C1 (MetaCons "RestoreRequest'" PrefixI True) (S1 (MetaSel (Just Symbol "_rrDays") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)))

restoreRequest Source #

Arguments

:: Int

rrDays

-> RestoreRequest 

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 :: Lens' RestoreRequest Int Source #

Lifetime of the active copy in days

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 # 

Methods

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

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.4.4-HefXwCotGB7GxFwqy8ThdO" 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 :: 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 # 

Methods

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

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.4.4-HefXwCotGB7GxFwqy8ThdO" 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:

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 # 

Methods

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

type Rep S3ServiceError Source # 
type Rep S3ServiceError = D1 (MetaData "S3ServiceError" "Network.AWS.S3.Types.Product" "amazonka-s3-1.4.4-HefXwCotGB7GxFwqy8ThdO" 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.

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.4.4-HefXwCotGB7GxFwqy8ThdO" 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.4.4-HefXwCotGB7GxFwqy8ThdO" 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 # 

Methods

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

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.4.4-HefXwCotGB7GxFwqy8ThdO" 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 :: 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.4.4-HefXwCotGB7GxFwqy8ThdO" 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 :: 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 # 

Methods

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

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.4.4-HefXwCotGB7GxFwqy8ThdO" 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 :: 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.4.4-HefXwCotGB7GxFwqy8ThdO" 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:

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.4.4-HefXwCotGB7GxFwqy8ThdO" 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: