{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
module Network.AWS.S3.Types.Product where
import Network.AWS.Lens
import Network.AWS.Prelude
import Network.AWS.S3.Internal
import Network.AWS.S3.Types.Sum
newtype AbortIncompleteMultipartUpload = AbortIncompleteMultipartUpload'
{ _aimuDaysAfterInitiation :: Maybe Int
} deriving (Eq, Read, Show, Data, Typeable, Generic)
abortIncompleteMultipartUpload
:: AbortIncompleteMultipartUpload
abortIncompleteMultipartUpload =
AbortIncompleteMultipartUpload' {_aimuDaysAfterInitiation = Nothing}
aimuDaysAfterInitiation :: Lens' AbortIncompleteMultipartUpload (Maybe Int)
aimuDaysAfterInitiation = lens _aimuDaysAfterInitiation (\ s a -> s{_aimuDaysAfterInitiation = a})
instance FromXML AbortIncompleteMultipartUpload where
parseXML x
= AbortIncompleteMultipartUpload' <$>
(x .@? "DaysAfterInitiation")
instance Hashable AbortIncompleteMultipartUpload
where
instance NFData AbortIncompleteMultipartUpload where
instance ToXML AbortIncompleteMultipartUpload where
toXML AbortIncompleteMultipartUpload'{..}
= mconcat
["DaysAfterInitiation" @= _aimuDaysAfterInitiation]
newtype AccelerateConfiguration = AccelerateConfiguration'
{ _acStatus :: Maybe BucketAccelerateStatus
} deriving (Eq, Read, Show, Data, Typeable, Generic)
accelerateConfiguration
:: AccelerateConfiguration
accelerateConfiguration = AccelerateConfiguration' {_acStatus = Nothing}
acStatus :: Lens' AccelerateConfiguration (Maybe BucketAccelerateStatus)
acStatus = lens _acStatus (\ s a -> s{_acStatus = a})
instance Hashable AccelerateConfiguration where
instance NFData AccelerateConfiguration where
instance ToXML AccelerateConfiguration where
toXML AccelerateConfiguration'{..}
= mconcat ["Status" @= _acStatus]
data AccessControlPolicy = AccessControlPolicy'
{ _acpGrants :: !(Maybe [Grant])
, _acpOwner :: !(Maybe Owner)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
accessControlPolicy
:: AccessControlPolicy
accessControlPolicy =
AccessControlPolicy' {_acpGrants = Nothing, _acpOwner = Nothing}
acpGrants :: Lens' AccessControlPolicy [Grant]
acpGrants = lens _acpGrants (\ s a -> s{_acpGrants = a}) . _Default . _Coerce
acpOwner :: Lens' AccessControlPolicy (Maybe Owner)
acpOwner = lens _acpOwner (\ s a -> s{_acpOwner = a})
instance Hashable AccessControlPolicy where
instance NFData AccessControlPolicy where
instance ToXML AccessControlPolicy where
toXML AccessControlPolicy'{..}
= mconcat
["AccessControlList" @=
toXML (toXMLList "Grant" <$> _acpGrants),
"Owner" @= _acpOwner]
newtype AccessControlTranslation = AccessControlTranslation'
{ _actOwner :: OwnerOverride
} deriving (Eq, Read, Show, Data, Typeable, Generic)
accessControlTranslation
:: OwnerOverride
-> AccessControlTranslation
accessControlTranslation pOwner_ =
AccessControlTranslation' {_actOwner = pOwner_}
actOwner :: Lens' AccessControlTranslation OwnerOverride
actOwner = lens _actOwner (\ s a -> s{_actOwner = a})
instance FromXML AccessControlTranslation where
parseXML x
= AccessControlTranslation' <$> (x .@ "Owner")
instance Hashable AccessControlTranslation where
instance NFData AccessControlTranslation where
instance ToXML AccessControlTranslation where
toXML AccessControlTranslation'{..}
= mconcat ["Owner" @= _actOwner]
data AnalyticsAndOperator = AnalyticsAndOperator'
{ _aaoPrefix :: !(Maybe Text)
, _aaoTags :: !(Maybe [Tag])
} deriving (Eq, Read, Show, Data, Typeable, Generic)
analyticsAndOperator
:: AnalyticsAndOperator
analyticsAndOperator =
AnalyticsAndOperator' {_aaoPrefix = Nothing, _aaoTags = Nothing}
aaoPrefix :: Lens' AnalyticsAndOperator (Maybe Text)
aaoPrefix = lens _aaoPrefix (\ s a -> s{_aaoPrefix = a})
aaoTags :: Lens' AnalyticsAndOperator [Tag]
aaoTags = lens _aaoTags (\ s a -> s{_aaoTags = a}) . _Default . _Coerce
instance FromXML AnalyticsAndOperator where
parseXML x
= AnalyticsAndOperator' <$>
(x .@? "Prefix") <*>
(x .@? "Tag" .!@ mempty >>= may (parseXMLList "Tag"))
instance Hashable AnalyticsAndOperator where
instance NFData AnalyticsAndOperator where
instance ToXML AnalyticsAndOperator where
toXML AnalyticsAndOperator'{..}
= mconcat
["Prefix" @= _aaoPrefix,
"Tag" @= toXML (toXMLList "Tag" <$> _aaoTags)]
data AnalyticsConfiguration = AnalyticsConfiguration'
{ _acFilter :: !(Maybe AnalyticsFilter)
, _acId :: !Text
, _acStorageClassAnalysis :: !StorageClassAnalysis
} deriving (Eq, Read, Show, Data, Typeable, Generic)
analyticsConfiguration
:: Text
-> StorageClassAnalysis
-> AnalyticsConfiguration
analyticsConfiguration pId_ pStorageClassAnalysis_ =
AnalyticsConfiguration'
{ _acFilter = Nothing
, _acId = pId_
, _acStorageClassAnalysis = pStorageClassAnalysis_
}
acFilter :: Lens' AnalyticsConfiguration (Maybe AnalyticsFilter)
acFilter = lens _acFilter (\ s a -> s{_acFilter = a})
acId :: Lens' AnalyticsConfiguration Text
acId = lens _acId (\ s a -> s{_acId = a})
acStorageClassAnalysis :: Lens' AnalyticsConfiguration StorageClassAnalysis
acStorageClassAnalysis = lens _acStorageClassAnalysis (\ s a -> s{_acStorageClassAnalysis = a})
instance FromXML AnalyticsConfiguration where
parseXML x
= AnalyticsConfiguration' <$>
(x .@? "Filter") <*> (x .@ "Id") <*>
(x .@ "StorageClassAnalysis")
instance Hashable AnalyticsConfiguration where
instance NFData AnalyticsConfiguration where
instance ToXML AnalyticsConfiguration where
toXML AnalyticsConfiguration'{..}
= mconcat
["Filter" @= _acFilter, "Id" @= _acId,
"StorageClassAnalysis" @= _acStorageClassAnalysis]
newtype AnalyticsExportDestination = AnalyticsExportDestination'
{ _aedS3BucketDestination :: AnalyticsS3BucketDestination
} deriving (Eq, Read, Show, Data, Typeable, Generic)
analyticsExportDestination
:: AnalyticsS3BucketDestination
-> AnalyticsExportDestination
analyticsExportDestination pS3BucketDestination_ =
AnalyticsExportDestination' {_aedS3BucketDestination = pS3BucketDestination_}
aedS3BucketDestination :: Lens' AnalyticsExportDestination AnalyticsS3BucketDestination
aedS3BucketDestination = lens _aedS3BucketDestination (\ s a -> s{_aedS3BucketDestination = a})
instance FromXML AnalyticsExportDestination where
parseXML x
= AnalyticsExportDestination' <$>
(x .@ "S3BucketDestination")
instance Hashable AnalyticsExportDestination where
instance NFData AnalyticsExportDestination where
instance ToXML AnalyticsExportDestination where
toXML AnalyticsExportDestination'{..}
= mconcat
["S3BucketDestination" @= _aedS3BucketDestination]
data AnalyticsFilter = AnalyticsFilter'
{ _afTag :: !(Maybe Tag)
, _afPrefix :: !(Maybe Text)
, _afAnd :: !(Maybe AnalyticsAndOperator)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
analyticsFilter
:: AnalyticsFilter
analyticsFilter =
AnalyticsFilter' {_afTag = Nothing, _afPrefix = Nothing, _afAnd = Nothing}
afTag :: Lens' AnalyticsFilter (Maybe Tag)
afTag = lens _afTag (\ s a -> s{_afTag = a})
afPrefix :: Lens' AnalyticsFilter (Maybe Text)
afPrefix = lens _afPrefix (\ s a -> s{_afPrefix = a})
afAnd :: Lens' AnalyticsFilter (Maybe AnalyticsAndOperator)
afAnd = lens _afAnd (\ s a -> s{_afAnd = a})
instance FromXML AnalyticsFilter where
parseXML x
= AnalyticsFilter' <$>
(x .@? "Tag") <*> (x .@? "Prefix") <*> (x .@? "And")
instance Hashable AnalyticsFilter where
instance NFData AnalyticsFilter where
instance ToXML AnalyticsFilter where
toXML AnalyticsFilter'{..}
= mconcat
["Tag" @= _afTag, "Prefix" @= _afPrefix,
"And" @= _afAnd]
data AnalyticsS3BucketDestination = AnalyticsS3BucketDestination'
{ _asbdBucketAccountId :: !(Maybe Text)
, _asbdPrefix :: !(Maybe Text)
, _asbdFormat :: !AnalyticsS3ExportFileFormat
, _asbdBucket :: !BucketName
} deriving (Eq, Read, Show, Data, Typeable, Generic)
analyticsS3BucketDestination
:: AnalyticsS3ExportFileFormat
-> BucketName
-> AnalyticsS3BucketDestination
analyticsS3BucketDestination pFormat_ pBucket_ =
AnalyticsS3BucketDestination'
{ _asbdBucketAccountId = Nothing
, _asbdPrefix = Nothing
, _asbdFormat = pFormat_
, _asbdBucket = pBucket_
}
asbdBucketAccountId :: Lens' AnalyticsS3BucketDestination (Maybe Text)
asbdBucketAccountId = lens _asbdBucketAccountId (\ s a -> s{_asbdBucketAccountId = a})
asbdPrefix :: Lens' AnalyticsS3BucketDestination (Maybe Text)
asbdPrefix = lens _asbdPrefix (\ s a -> s{_asbdPrefix = a})
asbdFormat :: Lens' AnalyticsS3BucketDestination AnalyticsS3ExportFileFormat
asbdFormat = lens _asbdFormat (\ s a -> s{_asbdFormat = a})
asbdBucket :: Lens' AnalyticsS3BucketDestination BucketName
asbdBucket = lens _asbdBucket (\ s a -> s{_asbdBucket = a})
instance FromXML AnalyticsS3BucketDestination where
parseXML x
= AnalyticsS3BucketDestination' <$>
(x .@? "BucketAccountId") <*> (x .@? "Prefix") <*>
(x .@ "Format")
<*> (x .@ "Bucket")
instance Hashable AnalyticsS3BucketDestination where
instance NFData AnalyticsS3BucketDestination where
instance ToXML AnalyticsS3BucketDestination where
toXML AnalyticsS3BucketDestination'{..}
= mconcat
["BucketAccountId" @= _asbdBucketAccountId,
"Prefix" @= _asbdPrefix, "Format" @= _asbdFormat,
"Bucket" @= _asbdBucket]
data Bucket = Bucket'
{ _bCreationDate :: !RFC822
, _bName :: !BucketName
} deriving (Eq, Read, Show, Data, Typeable, Generic)
bucket
:: UTCTime
-> BucketName
-> Bucket
bucket pCreationDate_ pName_ =
Bucket' {_bCreationDate = _Time # pCreationDate_, _bName = pName_}
bCreationDate :: Lens' Bucket UTCTime
bCreationDate = lens _bCreationDate (\ s a -> s{_bCreationDate = a}) . _Time
bName :: Lens' Bucket BucketName
bName = lens _bName (\ s a -> s{_bName = a})
instance FromXML Bucket where
parseXML x
= Bucket' <$> (x .@ "CreationDate") <*> (x .@ "Name")
instance Hashable Bucket where
instance NFData Bucket where
newtype BucketLifecycleConfiguration = BucketLifecycleConfiguration'
{ _blcRules :: [LifecycleRule]
} deriving (Eq, Read, Show, Data, Typeable, Generic)
bucketLifecycleConfiguration
:: BucketLifecycleConfiguration
bucketLifecycleConfiguration =
BucketLifecycleConfiguration' {_blcRules = mempty}
blcRules :: Lens' BucketLifecycleConfiguration [LifecycleRule]
blcRules = lens _blcRules (\ s a -> s{_blcRules = a}) . _Coerce
instance Hashable BucketLifecycleConfiguration where
instance NFData BucketLifecycleConfiguration where
instance ToXML BucketLifecycleConfiguration where
toXML BucketLifecycleConfiguration'{..}
= mconcat [toXMLList "Rule" _blcRules]
newtype BucketLoggingStatus = BucketLoggingStatus'
{ _blsLoggingEnabled :: Maybe LoggingEnabled
} deriving (Eq, Read, Show, Data, Typeable, Generic)
bucketLoggingStatus
:: BucketLoggingStatus
bucketLoggingStatus = BucketLoggingStatus' {_blsLoggingEnabled = Nothing}
blsLoggingEnabled :: Lens' BucketLoggingStatus (Maybe LoggingEnabled)
blsLoggingEnabled = lens _blsLoggingEnabled (\ s a -> s{_blsLoggingEnabled = a})
instance Hashable BucketLoggingStatus where
instance NFData BucketLoggingStatus where
instance ToXML BucketLoggingStatus where
toXML BucketLoggingStatus'{..}
= mconcat ["LoggingEnabled" @= _blsLoggingEnabled]
newtype CORSConfiguration = CORSConfiguration'
{ _ccCORSRules :: [CORSRule]
} deriving (Eq, Read, Show, Data, Typeable, Generic)
corsConfiguration
:: CORSConfiguration
corsConfiguration = CORSConfiguration' {_ccCORSRules = mempty}
ccCORSRules :: Lens' CORSConfiguration [CORSRule]
ccCORSRules = lens _ccCORSRules (\ s a -> s{_ccCORSRules = a}) . _Coerce
instance Hashable CORSConfiguration where
instance NFData CORSConfiguration where
instance ToXML CORSConfiguration where
toXML CORSConfiguration'{..}
= mconcat [toXMLList "CORSRule" _ccCORSRules]
data CORSRule = CORSRule'
{ _crMaxAgeSeconds :: !(Maybe Int)
, _crAllowedHeaders :: !(Maybe [Text])
, _crExposeHeaders :: !(Maybe [Text])
, _crAllowedMethods :: ![Text]
, _crAllowedOrigins :: ![Text]
} deriving (Eq, Read, Show, Data, Typeable, Generic)
corsRule
:: CORSRule
corsRule =
CORSRule'
{ _crMaxAgeSeconds = Nothing
, _crAllowedHeaders = Nothing
, _crExposeHeaders = Nothing
, _crAllowedMethods = mempty
, _crAllowedOrigins = mempty
}
crMaxAgeSeconds :: Lens' CORSRule (Maybe Int)
crMaxAgeSeconds = lens _crMaxAgeSeconds (\ s a -> s{_crMaxAgeSeconds = a})
crAllowedHeaders :: Lens' CORSRule [Text]
crAllowedHeaders = lens _crAllowedHeaders (\ s a -> s{_crAllowedHeaders = a}) . _Default . _Coerce
crExposeHeaders :: Lens' CORSRule [Text]
crExposeHeaders = lens _crExposeHeaders (\ s a -> s{_crExposeHeaders = a}) . _Default . _Coerce
crAllowedMethods :: Lens' CORSRule [Text]
crAllowedMethods = lens _crAllowedMethods (\ s a -> s{_crAllowedMethods = a}) . _Coerce
crAllowedOrigins :: Lens' CORSRule [Text]
crAllowedOrigins = lens _crAllowedOrigins (\ s a -> s{_crAllowedOrigins = a}) . _Coerce
instance FromXML CORSRule where
parseXML x
= CORSRule' <$>
(x .@? "MaxAgeSeconds") <*>
(may (parseXMLList "AllowedHeader") x)
<*> (may (parseXMLList "ExposeHeader") x)
<*> (parseXMLList "AllowedMethod" x)
<*> (parseXMLList "AllowedOrigin" x)
instance Hashable CORSRule where
instance NFData CORSRule where
instance ToXML CORSRule where
toXML CORSRule'{..}
= mconcat
["MaxAgeSeconds" @= _crMaxAgeSeconds,
toXML
(toXMLList "AllowedHeader" <$> _crAllowedHeaders),
toXML
(toXMLList "ExposeHeader" <$> _crExposeHeaders),
toXMLList "AllowedMethod" _crAllowedMethods,
toXMLList "AllowedOrigin" _crAllowedOrigins]
data CSVInput = CSVInput'
{ _ciQuoteCharacter :: !(Maybe Text)
, _ciRecordDelimiter :: !(Maybe Text)
, _ciFileHeaderInfo :: !(Maybe FileHeaderInfo)
, _ciQuoteEscapeCharacter :: !(Maybe Text)
, _ciComments :: !(Maybe Text)
, _ciFieldDelimiter :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
csvInput
:: CSVInput
csvInput =
CSVInput'
{ _ciQuoteCharacter = Nothing
, _ciRecordDelimiter = Nothing
, _ciFileHeaderInfo = Nothing
, _ciQuoteEscapeCharacter = Nothing
, _ciComments = Nothing
, _ciFieldDelimiter = Nothing
}
ciQuoteCharacter :: Lens' CSVInput (Maybe Text)
ciQuoteCharacter = lens _ciQuoteCharacter (\ s a -> s{_ciQuoteCharacter = a})
ciRecordDelimiter :: Lens' CSVInput (Maybe Text)
ciRecordDelimiter = lens _ciRecordDelimiter (\ s a -> s{_ciRecordDelimiter = a})
ciFileHeaderInfo :: Lens' CSVInput (Maybe FileHeaderInfo)
ciFileHeaderInfo = lens _ciFileHeaderInfo (\ s a -> s{_ciFileHeaderInfo = a})
ciQuoteEscapeCharacter :: Lens' CSVInput (Maybe Text)
ciQuoteEscapeCharacter = lens _ciQuoteEscapeCharacter (\ s a -> s{_ciQuoteEscapeCharacter = a})
ciComments :: Lens' CSVInput (Maybe Text)
ciComments = lens _ciComments (\ s a -> s{_ciComments = a})
ciFieldDelimiter :: Lens' CSVInput (Maybe Text)
ciFieldDelimiter = lens _ciFieldDelimiter (\ s a -> s{_ciFieldDelimiter = a})
instance Hashable CSVInput where
instance NFData CSVInput where
instance ToXML CSVInput where
toXML CSVInput'{..}
= mconcat
["QuoteCharacter" @= _ciQuoteCharacter,
"RecordDelimiter" @= _ciRecordDelimiter,
"FileHeaderInfo" @= _ciFileHeaderInfo,
"QuoteEscapeCharacter" @= _ciQuoteEscapeCharacter,
"Comments" @= _ciComments,
"FieldDelimiter" @= _ciFieldDelimiter]
data CSVOutput = CSVOutput'
{ _coQuoteCharacter :: !(Maybe Text)
, _coQuoteFields :: !(Maybe QuoteFields)
, _coRecordDelimiter :: !(Maybe Text)
, _coQuoteEscapeCharacter :: !(Maybe Text)
, _coFieldDelimiter :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
csvOutput
:: CSVOutput
csvOutput =
CSVOutput'
{ _coQuoteCharacter = Nothing
, _coQuoteFields = Nothing
, _coRecordDelimiter = Nothing
, _coQuoteEscapeCharacter = Nothing
, _coFieldDelimiter = Nothing
}
coQuoteCharacter :: Lens' CSVOutput (Maybe Text)
coQuoteCharacter = lens _coQuoteCharacter (\ s a -> s{_coQuoteCharacter = a})
coQuoteFields :: Lens' CSVOutput (Maybe QuoteFields)
coQuoteFields = lens _coQuoteFields (\ s a -> s{_coQuoteFields = a})
coRecordDelimiter :: Lens' CSVOutput (Maybe Text)
coRecordDelimiter = lens _coRecordDelimiter (\ s a -> s{_coRecordDelimiter = a})
coQuoteEscapeCharacter :: Lens' CSVOutput (Maybe Text)
coQuoteEscapeCharacter = lens _coQuoteEscapeCharacter (\ s a -> s{_coQuoteEscapeCharacter = a})
coFieldDelimiter :: Lens' CSVOutput (Maybe Text)
coFieldDelimiter = lens _coFieldDelimiter (\ s a -> s{_coFieldDelimiter = a})
instance Hashable CSVOutput where
instance NFData CSVOutput where
instance ToXML CSVOutput where
toXML CSVOutput'{..}
= mconcat
["QuoteCharacter" @= _coQuoteCharacter,
"QuoteFields" @= _coQuoteFields,
"RecordDelimiter" @= _coRecordDelimiter,
"QuoteEscapeCharacter" @= _coQuoteEscapeCharacter,
"FieldDelimiter" @= _coFieldDelimiter]
newtype CommonPrefix = CommonPrefix'
{ _cpPrefix :: Maybe Text
} deriving (Eq, Read, Show, Data, Typeable, Generic)
commonPrefix
:: CommonPrefix
commonPrefix = CommonPrefix' {_cpPrefix = Nothing}
cpPrefix :: Lens' CommonPrefix (Maybe Text)
cpPrefix = lens _cpPrefix (\ s a -> s{_cpPrefix = a})
instance FromXML CommonPrefix where
parseXML x = CommonPrefix' <$> (x .@? "Prefix")
instance Hashable CommonPrefix where
instance NFData CommonPrefix where
newtype CompletedMultipartUpload = CompletedMultipartUpload'
{ _cmuParts :: Maybe (List1 CompletedPart)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
completedMultipartUpload
:: CompletedMultipartUpload
completedMultipartUpload = CompletedMultipartUpload' {_cmuParts = Nothing}
cmuParts :: Lens' CompletedMultipartUpload (Maybe (NonEmpty CompletedPart))
cmuParts = lens _cmuParts (\ s a -> s{_cmuParts = a}) . mapping _List1
instance Hashable CompletedMultipartUpload where
instance NFData CompletedMultipartUpload where
instance ToXML CompletedMultipartUpload where
toXML CompletedMultipartUpload'{..}
= mconcat [toXML (toXMLList "Part" <$> _cmuParts)]
data CompletedPart = CompletedPart'
{ _cpPartNumber :: !Int
, _cpETag :: !ETag
} deriving (Eq, Read, Show, Data, Typeable, Generic)
completedPart
:: Int
-> ETag
-> CompletedPart
completedPart pPartNumber_ pETag_ =
CompletedPart' {_cpPartNumber = pPartNumber_, _cpETag = pETag_}
cpPartNumber :: Lens' CompletedPart Int
cpPartNumber = lens _cpPartNumber (\ s a -> s{_cpPartNumber = a})
cpETag :: Lens' CompletedPart ETag
cpETag = lens _cpETag (\ s a -> s{_cpETag = a})
instance Hashable CompletedPart where
instance NFData CompletedPart where
instance ToXML CompletedPart where
toXML CompletedPart'{..}
= mconcat
["PartNumber" @= _cpPartNumber, "ETag" @= _cpETag]
data Condition = Condition'
{ _cKeyPrefixEquals :: !(Maybe Text)
, _cHTTPErrorCodeReturnedEquals :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
condition
:: Condition
condition =
Condition'
{_cKeyPrefixEquals = Nothing, _cHTTPErrorCodeReturnedEquals = Nothing}
cKeyPrefixEquals :: Lens' Condition (Maybe Text)
cKeyPrefixEquals = lens _cKeyPrefixEquals (\ s a -> s{_cKeyPrefixEquals = a})
cHTTPErrorCodeReturnedEquals :: Lens' Condition (Maybe Text)
cHTTPErrorCodeReturnedEquals = lens _cHTTPErrorCodeReturnedEquals (\ s a -> s{_cHTTPErrorCodeReturnedEquals = a})
instance FromXML Condition where
parseXML x
= Condition' <$>
(x .@? "KeyPrefixEquals") <*>
(x .@? "HttpErrorCodeReturnedEquals")
instance Hashable Condition where
instance NFData Condition where
instance ToXML Condition where
toXML Condition'{..}
= mconcat
["KeyPrefixEquals" @= _cKeyPrefixEquals,
"HttpErrorCodeReturnedEquals" @=
_cHTTPErrorCodeReturnedEquals]
data ContinuationEvent =
ContinuationEvent'
deriving (Eq, Read, Show, Data, Typeable, Generic)
continuationEvent
:: ContinuationEvent
continuationEvent = ContinuationEvent'
instance FromXML ContinuationEvent where
parseXML = const (pure ContinuationEvent')
instance Hashable ContinuationEvent where
instance NFData ContinuationEvent where
data CopyObjectResult = CopyObjectResult'
{ _corETag :: !(Maybe ETag)
, _corLastModified :: !(Maybe RFC822)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
copyObjectResult
:: CopyObjectResult
copyObjectResult =
CopyObjectResult' {_corETag = Nothing, _corLastModified = Nothing}
corETag :: Lens' CopyObjectResult (Maybe ETag)
corETag = lens _corETag (\ s a -> s{_corETag = a})
corLastModified :: Lens' CopyObjectResult (Maybe UTCTime)
corLastModified = lens _corLastModified (\ s a -> s{_corLastModified = a}) . mapping _Time
instance FromXML CopyObjectResult where
parseXML x
= CopyObjectResult' <$>
(x .@? "ETag") <*> (x .@? "LastModified")
instance Hashable CopyObjectResult where
instance NFData CopyObjectResult where
data CopyPartResult = CopyPartResult'
{ _cprETag :: !(Maybe ETag)
, _cprLastModified :: !(Maybe RFC822)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
copyPartResult
:: CopyPartResult
copyPartResult =
CopyPartResult' {_cprETag = Nothing, _cprLastModified = Nothing}
cprETag :: Lens' CopyPartResult (Maybe ETag)
cprETag = lens _cprETag (\ s a -> s{_cprETag = a})
cprLastModified :: Lens' CopyPartResult (Maybe UTCTime)
cprLastModified = lens _cprLastModified (\ s a -> s{_cprLastModified = a}) . mapping _Time
instance FromXML CopyPartResult where
parseXML x
= CopyPartResult' <$>
(x .@? "ETag") <*> (x .@? "LastModified")
instance Hashable CopyPartResult where
instance NFData CopyPartResult where
newtype CreateBucketConfiguration = CreateBucketConfiguration'
{ _cbcLocationConstraint :: Maybe LocationConstraint
} deriving (Eq, Read, Show, Data, Typeable, Generic)
createBucketConfiguration
:: CreateBucketConfiguration
createBucketConfiguration =
CreateBucketConfiguration' {_cbcLocationConstraint = Nothing}
cbcLocationConstraint :: Lens' CreateBucketConfiguration (Maybe LocationConstraint)
cbcLocationConstraint = lens _cbcLocationConstraint (\ s a -> s{_cbcLocationConstraint = a})
instance Hashable CreateBucketConfiguration where
instance NFData CreateBucketConfiguration where
instance ToXML CreateBucketConfiguration where
toXML CreateBucketConfiguration'{..}
= mconcat
["LocationConstraint" @= _cbcLocationConstraint]
data Delete = Delete'
{ _dQuiet :: !(Maybe Bool)
, _dObjects :: ![ObjectIdentifier]
} deriving (Eq, Read, Show, Data, Typeable, Generic)
delete'
:: Delete
delete' = Delete' {_dQuiet = Nothing, _dObjects = mempty}
dQuiet :: Lens' Delete (Maybe Bool)
dQuiet = lens _dQuiet (\ s a -> s{_dQuiet = a})
dObjects :: Lens' Delete [ObjectIdentifier]
dObjects = lens _dObjects (\ s a -> s{_dObjects = a}) . _Coerce
instance Hashable Delete where
instance NFData Delete where
instance ToXML Delete where
toXML Delete'{..}
= mconcat
["Quiet" @= _dQuiet, toXMLList "Object" _dObjects]
data DeleteMarkerEntry = DeleteMarkerEntry'
{ _dmeVersionId :: !(Maybe ObjectVersionId)
, _dmeIsLatest :: !(Maybe Bool)
, _dmeOwner :: !(Maybe Owner)
, _dmeKey :: !(Maybe ObjectKey)
, _dmeLastModified :: !(Maybe RFC822)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
deleteMarkerEntry
:: DeleteMarkerEntry
deleteMarkerEntry =
DeleteMarkerEntry'
{ _dmeVersionId = Nothing
, _dmeIsLatest = Nothing
, _dmeOwner = Nothing
, _dmeKey = Nothing
, _dmeLastModified = Nothing
}
dmeVersionId :: Lens' DeleteMarkerEntry (Maybe ObjectVersionId)
dmeVersionId = lens _dmeVersionId (\ s a -> s{_dmeVersionId = a})
dmeIsLatest :: Lens' DeleteMarkerEntry (Maybe Bool)
dmeIsLatest = lens _dmeIsLatest (\ s a -> s{_dmeIsLatest = a})
dmeOwner :: Lens' DeleteMarkerEntry (Maybe Owner)
dmeOwner = lens _dmeOwner (\ s a -> s{_dmeOwner = a})
dmeKey :: Lens' DeleteMarkerEntry (Maybe ObjectKey)
dmeKey = lens _dmeKey (\ s a -> s{_dmeKey = a})
dmeLastModified :: Lens' DeleteMarkerEntry (Maybe UTCTime)
dmeLastModified = lens _dmeLastModified (\ s a -> s{_dmeLastModified = a}) . mapping _Time
instance FromXML DeleteMarkerEntry where
parseXML x
= DeleteMarkerEntry' <$>
(x .@? "VersionId") <*> (x .@? "IsLatest") <*>
(x .@? "Owner")
<*> (x .@? "Key")
<*> (x .@? "LastModified")
instance Hashable DeleteMarkerEntry where
instance NFData DeleteMarkerEntry where
data DeletedObject = DeletedObject'
{ _dVersionId :: !(Maybe ObjectVersionId)
, _dDeleteMarker :: !(Maybe Bool)
, _dDeleteMarkerVersionId :: !(Maybe Text)
, _dKey :: !(Maybe ObjectKey)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
deletedObject
:: DeletedObject
deletedObject =
DeletedObject'
{ _dVersionId = Nothing
, _dDeleteMarker = Nothing
, _dDeleteMarkerVersionId = Nothing
, _dKey = Nothing
}
dVersionId :: Lens' DeletedObject (Maybe ObjectVersionId)
dVersionId = lens _dVersionId (\ s a -> s{_dVersionId = a})
dDeleteMarker :: Lens' DeletedObject (Maybe Bool)
dDeleteMarker = lens _dDeleteMarker (\ s a -> s{_dDeleteMarker = a})
dDeleteMarkerVersionId :: Lens' DeletedObject (Maybe Text)
dDeleteMarkerVersionId = lens _dDeleteMarkerVersionId (\ s a -> s{_dDeleteMarkerVersionId = a})
dKey :: Lens' DeletedObject (Maybe ObjectKey)
dKey = lens _dKey (\ s a -> s{_dKey = a})
instance FromXML DeletedObject where
parseXML x
= DeletedObject' <$>
(x .@? "VersionId") <*> (x .@? "DeleteMarker") <*>
(x .@? "DeleteMarkerVersionId")
<*> (x .@? "Key")
instance Hashable DeletedObject where
instance NFData DeletedObject where
data Destination = Destination'
{ _dAccessControlTranslation :: !(Maybe AccessControlTranslation)
, _dAccount :: !(Maybe Text)
, _dStorageClass :: !(Maybe StorageClass)
, _dEncryptionConfiguration :: !(Maybe EncryptionConfiguration)
, _dBucket :: !BucketName
} deriving (Eq, Read, Show, Data, Typeable, Generic)
destination
:: BucketName
-> Destination
destination pBucket_ =
Destination'
{ _dAccessControlTranslation = Nothing
, _dAccount = Nothing
, _dStorageClass = Nothing
, _dEncryptionConfiguration = Nothing
, _dBucket = pBucket_
}
dAccessControlTranslation :: Lens' Destination (Maybe AccessControlTranslation)
dAccessControlTranslation = lens _dAccessControlTranslation (\ s a -> s{_dAccessControlTranslation = a})
dAccount :: Lens' Destination (Maybe Text)
dAccount = lens _dAccount (\ s a -> s{_dAccount = a})
dStorageClass :: Lens' Destination (Maybe StorageClass)
dStorageClass = lens _dStorageClass (\ s a -> s{_dStorageClass = a})
dEncryptionConfiguration :: Lens' Destination (Maybe EncryptionConfiguration)
dEncryptionConfiguration = lens _dEncryptionConfiguration (\ s a -> s{_dEncryptionConfiguration = a})
dBucket :: Lens' Destination BucketName
dBucket = lens _dBucket (\ s a -> s{_dBucket = a})
instance FromXML Destination where
parseXML x
= Destination' <$>
(x .@? "AccessControlTranslation") <*>
(x .@? "Account")
<*> (x .@? "StorageClass")
<*> (x .@? "EncryptionConfiguration")
<*> (x .@ "Bucket")
instance Hashable Destination where
instance NFData Destination where
instance ToXML Destination where
toXML Destination'{..}
= mconcat
["AccessControlTranslation" @=
_dAccessControlTranslation,
"Account" @= _dAccount,
"StorageClass" @= _dStorageClass,
"EncryptionConfiguration" @=
_dEncryptionConfiguration,
"Bucket" @= _dBucket]
data Encryption = Encryption'
{ _eKMSKeyId :: !(Maybe (Sensitive Text))
, _eKMSContext :: !(Maybe Text)
, _eEncryptionType :: !ServerSideEncryption
} deriving (Eq, Show, Data, Typeable, Generic)
encryption
:: ServerSideEncryption
-> Encryption
encryption pEncryptionType_ =
Encryption'
{ _eKMSKeyId = Nothing
, _eKMSContext = Nothing
, _eEncryptionType = pEncryptionType_
}
eKMSKeyId :: Lens' Encryption (Maybe Text)
eKMSKeyId = lens _eKMSKeyId (\ s a -> s{_eKMSKeyId = a}) . mapping _Sensitive
eKMSContext :: Lens' Encryption (Maybe Text)
eKMSContext = lens _eKMSContext (\ s a -> s{_eKMSContext = a})
eEncryptionType :: Lens' Encryption ServerSideEncryption
eEncryptionType = lens _eEncryptionType (\ s a -> s{_eEncryptionType = a})
instance Hashable Encryption where
instance NFData Encryption where
instance ToXML Encryption where
toXML Encryption'{..}
= mconcat
["KMSKeyId" @= _eKMSKeyId,
"KMSContext" @= _eKMSContext,
"EncryptionType" @= _eEncryptionType]
newtype EncryptionConfiguration = EncryptionConfiguration'
{ _ecReplicaKMSKeyId :: Maybe Text
} deriving (Eq, Read, Show, Data, Typeable, Generic)
encryptionConfiguration
:: EncryptionConfiguration
encryptionConfiguration =
EncryptionConfiguration' {_ecReplicaKMSKeyId = Nothing}
ecReplicaKMSKeyId :: Lens' EncryptionConfiguration (Maybe Text)
ecReplicaKMSKeyId = lens _ecReplicaKMSKeyId (\ s a -> s{_ecReplicaKMSKeyId = a})
instance FromXML EncryptionConfiguration where
parseXML x
= EncryptionConfiguration' <$>
(x .@? "ReplicaKmsKeyID")
instance Hashable EncryptionConfiguration where
instance NFData EncryptionConfiguration where
instance ToXML EncryptionConfiguration where
toXML EncryptionConfiguration'{..}
= mconcat ["ReplicaKmsKeyID" @= _ecReplicaKMSKeyId]
data EndEvent =
EndEvent'
deriving (Eq, Read, Show, Data, Typeable, Generic)
endEvent
:: EndEvent
endEvent = EndEvent'
instance FromXML EndEvent where
parseXML = const (pure EndEvent')
instance Hashable EndEvent where
instance NFData EndEvent where
newtype ErrorDocument = ErrorDocument'
{ _edKey :: ObjectKey
} deriving (Eq, Read, Show, Data, Typeable, Generic)
errorDocument
:: ObjectKey
-> ErrorDocument
errorDocument pKey_ = ErrorDocument' {_edKey = pKey_}
edKey :: Lens' ErrorDocument ObjectKey
edKey = lens _edKey (\ s a -> s{_edKey = a})
instance FromXML ErrorDocument where
parseXML x = ErrorDocument' <$> (x .@ "Key")
instance Hashable ErrorDocument where
instance NFData ErrorDocument where
instance ToXML ErrorDocument where
toXML ErrorDocument'{..} = mconcat ["Key" @= _edKey]
data FilterRule = FilterRule'
{ _frValue :: !(Maybe Text)
, _frName :: !(Maybe FilterRuleName)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
filterRule
:: FilterRule
filterRule = FilterRule' {_frValue = Nothing, _frName = Nothing}
frValue :: Lens' FilterRule (Maybe Text)
frValue = lens _frValue (\ s a -> s{_frValue = a})
frName :: Lens' FilterRule (Maybe FilterRuleName)
frName = lens _frName (\ s a -> s{_frName = a})
instance FromXML FilterRule where
parseXML x
= FilterRule' <$> (x .@? "Value") <*> (x .@? "Name")
instance Hashable FilterRule where
instance NFData FilterRule where
instance ToXML FilterRule where
toXML FilterRule'{..}
= mconcat ["Value" @= _frValue, "Name" @= _frName]
newtype GlacierJobParameters = GlacierJobParameters'
{ _gjpTier :: Tier
} deriving (Eq, Read, Show, Data, Typeable, Generic)
glacierJobParameters
:: Tier
-> GlacierJobParameters
glacierJobParameters pTier_ = GlacierJobParameters' {_gjpTier = pTier_}
gjpTier :: Lens' GlacierJobParameters Tier
gjpTier = lens _gjpTier (\ s a -> s{_gjpTier = a})
instance Hashable GlacierJobParameters where
instance NFData GlacierJobParameters where
instance ToXML GlacierJobParameters where
toXML GlacierJobParameters'{..}
= mconcat ["Tier" @= _gjpTier]
data Grant = Grant'
{ _gPermission :: !(Maybe Permission)
, _gGrantee :: !(Maybe Grantee)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
grant
:: Grant
grant = Grant' {_gPermission = Nothing, _gGrantee = Nothing}
gPermission :: Lens' Grant (Maybe Permission)
gPermission = lens _gPermission (\ s a -> s{_gPermission = a})
gGrantee :: Lens' Grant (Maybe Grantee)
gGrantee = lens _gGrantee (\ s a -> s{_gGrantee = a})
instance FromXML Grant where
parseXML x
= Grant' <$>
(x .@? "Permission") <*> (x .@? "Grantee")
instance Hashable Grant where
instance NFData Grant where
instance ToXML Grant where
toXML Grant'{..}
= mconcat
["Permission" @= _gPermission,
"Grantee" @= _gGrantee]
data Grantee = Grantee'
{ _gURI :: !(Maybe Text)
, _gEmailAddress :: !(Maybe Text)
, _gDisplayName :: !(Maybe Text)
, _gId :: !(Maybe Text)
, _gType :: !Type
} deriving (Eq, Read, Show, Data, Typeable, Generic)
grantee
:: Type
-> Grantee
grantee pType_ =
Grantee'
{ _gURI = Nothing
, _gEmailAddress = Nothing
, _gDisplayName = Nothing
, _gId = Nothing
, _gType = pType_
}
gURI :: Lens' Grantee (Maybe Text)
gURI = lens _gURI (\ s a -> s{_gURI = a})
gEmailAddress :: Lens' Grantee (Maybe Text)
gEmailAddress = lens _gEmailAddress (\ s a -> s{_gEmailAddress = a})
gDisplayName :: Lens' Grantee (Maybe Text)
gDisplayName = lens _gDisplayName (\ s a -> s{_gDisplayName = a})
gId :: Lens' Grantee (Maybe Text)
gId = lens _gId (\ s a -> s{_gId = a})
gType :: Lens' Grantee Type
gType = lens _gType (\ s a -> s{_gType = a})
instance FromXML Grantee where
parseXML x
= Grantee' <$>
(x .@? "URI") <*> (x .@? "EmailAddress") <*>
(x .@? "DisplayName")
<*> (x .@? "ID")
<*> (x .@ "xsi:type")
instance Hashable Grantee where
instance NFData Grantee where
instance ToXML Grantee where
toXML Grantee'{..}
= mconcat
["URI" @= _gURI, "EmailAddress" @= _gEmailAddress,
"DisplayName" @= _gDisplayName, "ID" @= _gId,
"xsi:type" @@= _gType]
newtype IndexDocument = IndexDocument'
{ _idSuffix :: Text
} deriving (Eq, Read, Show, Data, Typeable, Generic)
indexDocument
:: Text
-> IndexDocument
indexDocument pSuffix_ = IndexDocument' {_idSuffix = pSuffix_}
idSuffix :: Lens' IndexDocument Text
idSuffix = lens _idSuffix (\ s a -> s{_idSuffix = a})
instance FromXML IndexDocument where
parseXML x = IndexDocument' <$> (x .@ "Suffix")
instance Hashable IndexDocument where
instance NFData IndexDocument where
instance ToXML IndexDocument where
toXML IndexDocument'{..}
= mconcat ["Suffix" @= _idSuffix]
data Initiator = Initiator'
{ _iDisplayName :: !(Maybe Text)
, _iId :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
initiator
:: Initiator
initiator = Initiator' {_iDisplayName = Nothing, _iId = Nothing}
iDisplayName :: Lens' Initiator (Maybe Text)
iDisplayName = lens _iDisplayName (\ s a -> s{_iDisplayName = a})
iId :: Lens' Initiator (Maybe Text)
iId = lens _iId (\ s a -> s{_iId = a})
instance FromXML Initiator where
parseXML x
= Initiator' <$>
(x .@? "DisplayName") <*> (x .@? "ID")
instance Hashable Initiator where
instance NFData Initiator where
data InputSerialization = InputSerialization'
{ _isJSON :: !(Maybe JSONInput)
, _isCSV :: !(Maybe CSVInput)
, _isCompressionType :: !(Maybe CompressionType)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
inputSerialization
:: InputSerialization
inputSerialization =
InputSerialization'
{_isJSON = Nothing, _isCSV = Nothing, _isCompressionType = Nothing}
isJSON :: Lens' InputSerialization (Maybe JSONInput)
isJSON = lens _isJSON (\ s a -> s{_isJSON = a})
isCSV :: Lens' InputSerialization (Maybe CSVInput)
isCSV = lens _isCSV (\ s a -> s{_isCSV = a})
isCompressionType :: Lens' InputSerialization (Maybe CompressionType)
isCompressionType = lens _isCompressionType (\ s a -> s{_isCompressionType = a})
instance Hashable InputSerialization where
instance NFData InputSerialization where
instance ToXML InputSerialization where
toXML InputSerialization'{..}
= mconcat
["JSON" @= _isJSON, "CSV" @= _isCSV,
"CompressionType" @= _isCompressionType]
data InventoryConfiguration = InventoryConfiguration'
{ _icOptionalFields :: !(Maybe [InventoryOptionalField])
, _icFilter :: !(Maybe InventoryFilter)
, _icDestination :: !InventoryDestination
, _icIsEnabled :: !Bool
, _icId :: !Text
, _icIncludedObjectVersions :: !InventoryIncludedObjectVersions
, _icSchedule :: !InventorySchedule
} deriving (Eq, Show, Data, Typeable, Generic)
inventoryConfiguration
:: InventoryDestination
-> Bool
-> Text
-> InventoryIncludedObjectVersions
-> InventorySchedule
-> InventoryConfiguration
inventoryConfiguration pDestination_ pIsEnabled_ pId_ pIncludedObjectVersions_ pSchedule_ =
InventoryConfiguration'
{ _icOptionalFields = Nothing
, _icFilter = Nothing
, _icDestination = pDestination_
, _icIsEnabled = pIsEnabled_
, _icId = pId_
, _icIncludedObjectVersions = pIncludedObjectVersions_
, _icSchedule = pSchedule_
}
icOptionalFields :: Lens' InventoryConfiguration [InventoryOptionalField]
icOptionalFields = lens _icOptionalFields (\ s a -> s{_icOptionalFields = a}) . _Default . _Coerce
icFilter :: Lens' InventoryConfiguration (Maybe InventoryFilter)
icFilter = lens _icFilter (\ s a -> s{_icFilter = a})
icDestination :: Lens' InventoryConfiguration InventoryDestination
icDestination = lens _icDestination (\ s a -> s{_icDestination = a})
icIsEnabled :: Lens' InventoryConfiguration Bool
icIsEnabled = lens _icIsEnabled (\ s a -> s{_icIsEnabled = a})
icId :: Lens' InventoryConfiguration Text
icId = lens _icId (\ s a -> s{_icId = a})
icIncludedObjectVersions :: Lens' InventoryConfiguration InventoryIncludedObjectVersions
icIncludedObjectVersions = lens _icIncludedObjectVersions (\ s a -> s{_icIncludedObjectVersions = a})
icSchedule :: Lens' InventoryConfiguration InventorySchedule
icSchedule = lens _icSchedule (\ s a -> s{_icSchedule = a})
instance FromXML InventoryConfiguration where
parseXML x
= InventoryConfiguration' <$>
(x .@? "OptionalFields" .!@ mempty >>=
may (parseXMLList "Field"))
<*> (x .@? "Filter")
<*> (x .@ "Destination")
<*> (x .@ "IsEnabled")
<*> (x .@ "Id")
<*> (x .@ "IncludedObjectVersions")
<*> (x .@ "Schedule")
instance Hashable InventoryConfiguration where
instance NFData InventoryConfiguration where
instance ToXML InventoryConfiguration where
toXML InventoryConfiguration'{..}
= mconcat
["OptionalFields" @=
toXML (toXMLList "Field" <$> _icOptionalFields),
"Filter" @= _icFilter,
"Destination" @= _icDestination,
"IsEnabled" @= _icIsEnabled, "Id" @= _icId,
"IncludedObjectVersions" @=
_icIncludedObjectVersions,
"Schedule" @= _icSchedule]
newtype InventoryDestination = InventoryDestination'
{ _idS3BucketDestination :: InventoryS3BucketDestination
} deriving (Eq, Show, Data, Typeable, Generic)
inventoryDestination
:: InventoryS3BucketDestination
-> InventoryDestination
inventoryDestination pS3BucketDestination_ =
InventoryDestination' {_idS3BucketDestination = pS3BucketDestination_}
idS3BucketDestination :: Lens' InventoryDestination InventoryS3BucketDestination
idS3BucketDestination = lens _idS3BucketDestination (\ s a -> s{_idS3BucketDestination = a})
instance FromXML InventoryDestination where
parseXML x
= InventoryDestination' <$>
(x .@ "S3BucketDestination")
instance Hashable InventoryDestination where
instance NFData InventoryDestination where
instance ToXML InventoryDestination where
toXML InventoryDestination'{..}
= mconcat
["S3BucketDestination" @= _idS3BucketDestination]
data InventoryEncryption = InventoryEncryption'
{ _ieSSES3 :: !(Maybe SSES3)
, _ieSSEKMS :: !(Maybe SSEKMS)
} deriving (Eq, Show, Data, Typeable, Generic)
inventoryEncryption
:: InventoryEncryption
inventoryEncryption =
InventoryEncryption' {_ieSSES3 = Nothing, _ieSSEKMS = Nothing}
ieSSES3 :: Lens' InventoryEncryption (Maybe SSES3)
ieSSES3 = lens _ieSSES3 (\ s a -> s{_ieSSES3 = a})
ieSSEKMS :: Lens' InventoryEncryption (Maybe SSEKMS)
ieSSEKMS = lens _ieSSEKMS (\ s a -> s{_ieSSEKMS = a})
instance FromXML InventoryEncryption where
parseXML x
= InventoryEncryption' <$>
(x .@? "SSE-S3") <*> (x .@? "SSE-KMS")
instance Hashable InventoryEncryption where
instance NFData InventoryEncryption where
instance ToXML InventoryEncryption where
toXML InventoryEncryption'{..}
= mconcat
["SSE-S3" @= _ieSSES3, "SSE-KMS" @= _ieSSEKMS]
newtype InventoryFilter = InventoryFilter'
{ _ifPrefix :: Text
} deriving (Eq, Read, Show, Data, Typeable, Generic)
inventoryFilter
:: Text
-> InventoryFilter
inventoryFilter pPrefix_ = InventoryFilter' {_ifPrefix = pPrefix_}
ifPrefix :: Lens' InventoryFilter Text
ifPrefix = lens _ifPrefix (\ s a -> s{_ifPrefix = a})
instance FromXML InventoryFilter where
parseXML x = InventoryFilter' <$> (x .@ "Prefix")
instance Hashable InventoryFilter where
instance NFData InventoryFilter where
instance ToXML InventoryFilter where
toXML InventoryFilter'{..}
= mconcat ["Prefix" @= _ifPrefix]
data InventoryS3BucketDestination = InventoryS3BucketDestination'
{ _isbdPrefix :: !(Maybe Text)
, _isbdAccountId :: !(Maybe Text)
, _isbdEncryption :: !(Maybe InventoryEncryption)
, _isbdBucket :: !BucketName
, _isbdFormat :: !InventoryFormat
} deriving (Eq, Show, Data, Typeable, Generic)
inventoryS3BucketDestination
:: BucketName
-> InventoryFormat
-> InventoryS3BucketDestination
inventoryS3BucketDestination pBucket_ pFormat_ =
InventoryS3BucketDestination'
{ _isbdPrefix = Nothing
, _isbdAccountId = Nothing
, _isbdEncryption = Nothing
, _isbdBucket = pBucket_
, _isbdFormat = pFormat_
}
isbdPrefix :: Lens' InventoryS3BucketDestination (Maybe Text)
isbdPrefix = lens _isbdPrefix (\ s a -> s{_isbdPrefix = a})
isbdAccountId :: Lens' InventoryS3BucketDestination (Maybe Text)
isbdAccountId = lens _isbdAccountId (\ s a -> s{_isbdAccountId = a})
isbdEncryption :: Lens' InventoryS3BucketDestination (Maybe InventoryEncryption)
isbdEncryption = lens _isbdEncryption (\ s a -> s{_isbdEncryption = a})
isbdBucket :: Lens' InventoryS3BucketDestination BucketName
isbdBucket = lens _isbdBucket (\ s a -> s{_isbdBucket = a})
isbdFormat :: Lens' InventoryS3BucketDestination InventoryFormat
isbdFormat = lens _isbdFormat (\ s a -> s{_isbdFormat = a})
instance FromXML InventoryS3BucketDestination where
parseXML x
= InventoryS3BucketDestination' <$>
(x .@? "Prefix") <*> (x .@? "AccountId") <*>
(x .@? "Encryption")
<*> (x .@ "Bucket")
<*> (x .@ "Format")
instance Hashable InventoryS3BucketDestination where
instance NFData InventoryS3BucketDestination where
instance ToXML InventoryS3BucketDestination where
toXML InventoryS3BucketDestination'{..}
= mconcat
["Prefix" @= _isbdPrefix,
"AccountId" @= _isbdAccountId,
"Encryption" @= _isbdEncryption,
"Bucket" @= _isbdBucket, "Format" @= _isbdFormat]
newtype InventorySchedule = InventorySchedule'
{ _isFrequency :: InventoryFrequency
} deriving (Eq, Read, Show, Data, Typeable, Generic)
inventorySchedule
:: InventoryFrequency
-> InventorySchedule
inventorySchedule pFrequency_ = InventorySchedule' {_isFrequency = pFrequency_}
isFrequency :: Lens' InventorySchedule InventoryFrequency
isFrequency = lens _isFrequency (\ s a -> s{_isFrequency = a})
instance FromXML InventorySchedule where
parseXML x
= InventorySchedule' <$> (x .@ "Frequency")
instance Hashable InventorySchedule where
instance NFData InventorySchedule where
instance ToXML InventorySchedule where
toXML InventorySchedule'{..}
= mconcat ["Frequency" @= _isFrequency]
newtype JSONInput = JSONInput'
{ _jiType :: Maybe JSONType
} deriving (Eq, Read, Show, Data, Typeable, Generic)
jsonInput
:: JSONInput
jsonInput = JSONInput' {_jiType = Nothing}
jiType :: Lens' JSONInput (Maybe JSONType)
jiType = lens _jiType (\ s a -> s{_jiType = a})
instance Hashable JSONInput where
instance NFData JSONInput where
instance ToXML JSONInput where
toXML JSONInput'{..} = mconcat ["Type" @= _jiType]
newtype JSONOutput = JSONOutput'
{ _joRecordDelimiter :: Maybe Text
} deriving (Eq, Read, Show, Data, Typeable, Generic)
jsonOutput
:: JSONOutput
jsonOutput = JSONOutput' {_joRecordDelimiter = Nothing}
joRecordDelimiter :: Lens' JSONOutput (Maybe Text)
joRecordDelimiter = lens _joRecordDelimiter (\ s a -> s{_joRecordDelimiter = a})
instance Hashable JSONOutput where
instance NFData JSONOutput where
instance ToXML JSONOutput where
toXML JSONOutput'{..}
= mconcat ["RecordDelimiter" @= _joRecordDelimiter]
data LambdaFunctionConfiguration = LambdaFunctionConfiguration'
{ _lfcId :: !(Maybe Text)
, _lfcFilter :: !(Maybe NotificationConfigurationFilter)
, _lfcLambdaFunctionARN :: !Text
, _lfcEvents :: ![Event]
} deriving (Eq, Read, Show, Data, Typeable, Generic)
lambdaFunctionConfiguration
:: Text
-> LambdaFunctionConfiguration
lambdaFunctionConfiguration pLambdaFunctionARN_ =
LambdaFunctionConfiguration'
{ _lfcId = Nothing
, _lfcFilter = Nothing
, _lfcLambdaFunctionARN = pLambdaFunctionARN_
, _lfcEvents = mempty
}
lfcId :: Lens' LambdaFunctionConfiguration (Maybe Text)
lfcId = lens _lfcId (\ s a -> s{_lfcId = a})
lfcFilter :: Lens' LambdaFunctionConfiguration (Maybe NotificationConfigurationFilter)
lfcFilter = lens _lfcFilter (\ s a -> s{_lfcFilter = a})
lfcLambdaFunctionARN :: Lens' LambdaFunctionConfiguration Text
lfcLambdaFunctionARN = lens _lfcLambdaFunctionARN (\ s a -> s{_lfcLambdaFunctionARN = a})
lfcEvents :: Lens' LambdaFunctionConfiguration [Event]
lfcEvents = lens _lfcEvents (\ s a -> s{_lfcEvents = a}) . _Coerce
instance FromXML LambdaFunctionConfiguration where
parseXML x
= LambdaFunctionConfiguration' <$>
(x .@? "Id") <*> (x .@? "Filter") <*>
(x .@ "CloudFunction")
<*> (parseXMLList "Event" x)
instance Hashable LambdaFunctionConfiguration where
instance NFData LambdaFunctionConfiguration where
instance ToXML LambdaFunctionConfiguration where
toXML LambdaFunctionConfiguration'{..}
= mconcat
["Id" @= _lfcId, "Filter" @= _lfcFilter,
"CloudFunction" @= _lfcLambdaFunctionARN,
toXMLList "Event" _lfcEvents]
data LifecycleExpiration = LifecycleExpiration'
{ _leDays :: !(Maybe Int)
, _leDate :: !(Maybe RFC822)
, _leExpiredObjectDeleteMarker :: !(Maybe Bool)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
lifecycleExpiration
:: LifecycleExpiration
lifecycleExpiration =
LifecycleExpiration'
{ _leDays = Nothing
, _leDate = Nothing
, _leExpiredObjectDeleteMarker = Nothing
}
leDays :: Lens' LifecycleExpiration (Maybe Int)
leDays = lens _leDays (\ s a -> s{_leDays = a})
leDate :: Lens' LifecycleExpiration (Maybe UTCTime)
leDate = lens _leDate (\ s a -> s{_leDate = a}) . mapping _Time
leExpiredObjectDeleteMarker :: Lens' LifecycleExpiration (Maybe Bool)
leExpiredObjectDeleteMarker = lens _leExpiredObjectDeleteMarker (\ s a -> s{_leExpiredObjectDeleteMarker = a})
instance FromXML LifecycleExpiration where
parseXML x
= LifecycleExpiration' <$>
(x .@? "Days") <*> (x .@? "Date") <*>
(x .@? "ExpiredObjectDeleteMarker")
instance Hashable LifecycleExpiration where
instance NFData LifecycleExpiration where
instance ToXML LifecycleExpiration where
toXML LifecycleExpiration'{..}
= mconcat
["Days" @= _leDays, "Date" @= _leDate,
"ExpiredObjectDeleteMarker" @=
_leExpiredObjectDeleteMarker]
data LifecycleRule = LifecycleRule'
{ _lrTransitions :: !(Maybe [Transition])
, _lrNoncurrentVersionExpiration :: !(Maybe NoncurrentVersionExpiration)
, _lrPrefix :: !(Maybe Text)
, _lrNoncurrentVersionTransitions :: !(Maybe [NoncurrentVersionTransition])
, _lrExpiration :: !(Maybe LifecycleExpiration)
, _lrId :: !(Maybe Text)
, _lrFilter :: !(Maybe LifecycleRuleFilter)
, _lrAbortIncompleteMultipartUpload :: !(Maybe AbortIncompleteMultipartUpload)
, _lrStatus :: !ExpirationStatus
} deriving (Eq, Read, Show, Data, Typeable, Generic)
lifecycleRule
:: ExpirationStatus
-> LifecycleRule
lifecycleRule pStatus_ =
LifecycleRule'
{ _lrTransitions = Nothing
, _lrNoncurrentVersionExpiration = Nothing
, _lrPrefix = Nothing
, _lrNoncurrentVersionTransitions = Nothing
, _lrExpiration = Nothing
, _lrId = Nothing
, _lrFilter = Nothing
, _lrAbortIncompleteMultipartUpload = Nothing
, _lrStatus = pStatus_
}
lrTransitions :: Lens' LifecycleRule [Transition]
lrTransitions = lens _lrTransitions (\ s a -> s{_lrTransitions = a}) . _Default . _Coerce
lrNoncurrentVersionExpiration :: Lens' LifecycleRule (Maybe NoncurrentVersionExpiration)
lrNoncurrentVersionExpiration = lens _lrNoncurrentVersionExpiration (\ s a -> s{_lrNoncurrentVersionExpiration = a})
lrPrefix :: Lens' LifecycleRule (Maybe Text)
lrPrefix = lens _lrPrefix (\ s a -> s{_lrPrefix = a})
lrNoncurrentVersionTransitions :: Lens' LifecycleRule [NoncurrentVersionTransition]
lrNoncurrentVersionTransitions = lens _lrNoncurrentVersionTransitions (\ s a -> s{_lrNoncurrentVersionTransitions = a}) . _Default . _Coerce
lrExpiration :: Lens' LifecycleRule (Maybe LifecycleExpiration)
lrExpiration = lens _lrExpiration (\ s a -> s{_lrExpiration = a})
lrId :: Lens' LifecycleRule (Maybe Text)
lrId = lens _lrId (\ s a -> s{_lrId = a})
lrFilter :: Lens' LifecycleRule (Maybe LifecycleRuleFilter)
lrFilter = lens _lrFilter (\ s a -> s{_lrFilter = a})
lrAbortIncompleteMultipartUpload :: Lens' LifecycleRule (Maybe AbortIncompleteMultipartUpload)
lrAbortIncompleteMultipartUpload = lens _lrAbortIncompleteMultipartUpload (\ s a -> s{_lrAbortIncompleteMultipartUpload = a})
lrStatus :: Lens' LifecycleRule ExpirationStatus
lrStatus = lens _lrStatus (\ s a -> s{_lrStatus = a})
instance FromXML LifecycleRule where
parseXML x
= LifecycleRule' <$>
(may (parseXMLList "Transition") x) <*>
(x .@? "NoncurrentVersionExpiration")
<*> (x .@? "Prefix")
<*>
(may (parseXMLList "NoncurrentVersionTransition") x)
<*> (x .@? "Expiration")
<*> (x .@? "ID")
<*> (x .@? "Filter")
<*> (x .@? "AbortIncompleteMultipartUpload")
<*> (x .@ "Status")
instance Hashable LifecycleRule where
instance NFData LifecycleRule where
instance ToXML LifecycleRule where
toXML LifecycleRule'{..}
= mconcat
[toXML (toXMLList "Transition" <$> _lrTransitions),
"NoncurrentVersionExpiration" @=
_lrNoncurrentVersionExpiration,
"Prefix" @= _lrPrefix,
toXML
(toXMLList "NoncurrentVersionTransition" <$>
_lrNoncurrentVersionTransitions),
"Expiration" @= _lrExpiration, "ID" @= _lrId,
"Filter" @= _lrFilter,
"AbortIncompleteMultipartUpload" @=
_lrAbortIncompleteMultipartUpload,
"Status" @= _lrStatus]
data LifecycleRuleAndOperator = LifecycleRuleAndOperator'
{ _lraoPrefix :: !(Maybe Text)
, _lraoTags :: !(Maybe [Tag])
} deriving (Eq, Read, Show, Data, Typeable, Generic)
lifecycleRuleAndOperator
:: LifecycleRuleAndOperator
lifecycleRuleAndOperator =
LifecycleRuleAndOperator' {_lraoPrefix = Nothing, _lraoTags = Nothing}
lraoPrefix :: Lens' LifecycleRuleAndOperator (Maybe Text)
lraoPrefix = lens _lraoPrefix (\ s a -> s{_lraoPrefix = a})
lraoTags :: Lens' LifecycleRuleAndOperator [Tag]
lraoTags = lens _lraoTags (\ s a -> s{_lraoTags = a}) . _Default . _Coerce
instance FromXML LifecycleRuleAndOperator where
parseXML x
= LifecycleRuleAndOperator' <$>
(x .@? "Prefix") <*>
(x .@? "Tag" .!@ mempty >>= may (parseXMLList "Tag"))
instance Hashable LifecycleRuleAndOperator where
instance NFData LifecycleRuleAndOperator where
instance ToXML LifecycleRuleAndOperator where
toXML LifecycleRuleAndOperator'{..}
= mconcat
["Prefix" @= _lraoPrefix,
"Tag" @= toXML (toXMLList "Tag" <$> _lraoTags)]
data LifecycleRuleFilter = LifecycleRuleFilter'
{ _lrfTag :: !(Maybe Tag)
, _lrfPrefix :: !(Maybe Text)
, _lrfAnd :: !(Maybe LifecycleRuleAndOperator)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
lifecycleRuleFilter
:: LifecycleRuleFilter
lifecycleRuleFilter =
LifecycleRuleFilter'
{_lrfTag = Nothing, _lrfPrefix = Nothing, _lrfAnd = Nothing}
lrfTag :: Lens' LifecycleRuleFilter (Maybe Tag)
lrfTag = lens _lrfTag (\ s a -> s{_lrfTag = a})
lrfPrefix :: Lens' LifecycleRuleFilter (Maybe Text)
lrfPrefix = lens _lrfPrefix (\ s a -> s{_lrfPrefix = a})
lrfAnd :: Lens' LifecycleRuleFilter (Maybe LifecycleRuleAndOperator)
lrfAnd = lens _lrfAnd (\ s a -> s{_lrfAnd = a})
instance FromXML LifecycleRuleFilter where
parseXML x
= LifecycleRuleFilter' <$>
(x .@? "Tag") <*> (x .@? "Prefix") <*> (x .@? "And")
instance Hashable LifecycleRuleFilter where
instance NFData LifecycleRuleFilter where
instance ToXML LifecycleRuleFilter where
toXML LifecycleRuleFilter'{..}
= mconcat
["Tag" @= _lrfTag, "Prefix" @= _lrfPrefix,
"And" @= _lrfAnd]
data LoggingEnabled = LoggingEnabled'
{ _leTargetGrants :: !(Maybe [TargetGrant])
, _leTargetBucket :: !Text
, _leTargetPrefix :: !Text
} deriving (Eq, Read, Show, Data, Typeable, Generic)
loggingEnabled
:: Text
-> Text
-> LoggingEnabled
loggingEnabled pTargetBucket_ pTargetPrefix_ =
LoggingEnabled'
{ _leTargetGrants = Nothing
, _leTargetBucket = pTargetBucket_
, _leTargetPrefix = pTargetPrefix_
}
leTargetGrants :: Lens' LoggingEnabled [TargetGrant]
leTargetGrants = lens _leTargetGrants (\ s a -> s{_leTargetGrants = a}) . _Default . _Coerce
leTargetBucket :: Lens' LoggingEnabled Text
leTargetBucket = lens _leTargetBucket (\ s a -> s{_leTargetBucket = a})
leTargetPrefix :: Lens' LoggingEnabled Text
leTargetPrefix = lens _leTargetPrefix (\ s a -> s{_leTargetPrefix = a})
instance FromXML LoggingEnabled where
parseXML x
= LoggingEnabled' <$>
(x .@? "TargetGrants" .!@ mempty >>=
may (parseXMLList "Grant"))
<*> (x .@ "TargetBucket")
<*> (x .@ "TargetPrefix")
instance Hashable LoggingEnabled where
instance NFData LoggingEnabled where
instance ToXML LoggingEnabled where
toXML LoggingEnabled'{..}
= mconcat
["TargetGrants" @=
toXML (toXMLList "Grant" <$> _leTargetGrants),
"TargetBucket" @= _leTargetBucket,
"TargetPrefix" @= _leTargetPrefix]
data MetadataEntry = MetadataEntry'
{ _meValue :: !(Maybe Text)
, _meName :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
metadataEntry
:: MetadataEntry
metadataEntry = MetadataEntry' {_meValue = Nothing, _meName = Nothing}
meValue :: Lens' MetadataEntry (Maybe Text)
meValue = lens _meValue (\ s a -> s{_meValue = a})
meName :: Lens' MetadataEntry (Maybe Text)
meName = lens _meName (\ s a -> s{_meName = a})
instance Hashable MetadataEntry where
instance NFData MetadataEntry where
instance ToXML MetadataEntry where
toXML MetadataEntry'{..}
= mconcat ["Value" @= _meValue, "Name" @= _meName]
data MetricsAndOperator = MetricsAndOperator'
{ _maoPrefix :: !(Maybe Text)
, _maoTags :: !(Maybe [Tag])
} deriving (Eq, Read, Show, Data, Typeable, Generic)
metricsAndOperator
:: MetricsAndOperator
metricsAndOperator =
MetricsAndOperator' {_maoPrefix = Nothing, _maoTags = Nothing}
maoPrefix :: Lens' MetricsAndOperator (Maybe Text)
maoPrefix = lens _maoPrefix (\ s a -> s{_maoPrefix = a})
maoTags :: Lens' MetricsAndOperator [Tag]
maoTags = lens _maoTags (\ s a -> s{_maoTags = a}) . _Default . _Coerce
instance FromXML MetricsAndOperator where
parseXML x
= MetricsAndOperator' <$>
(x .@? "Prefix") <*>
(x .@? "Tag" .!@ mempty >>= may (parseXMLList "Tag"))
instance Hashable MetricsAndOperator where
instance NFData MetricsAndOperator where
instance ToXML MetricsAndOperator where
toXML MetricsAndOperator'{..}
= mconcat
["Prefix" @= _maoPrefix,
"Tag" @= toXML (toXMLList "Tag" <$> _maoTags)]
data MetricsConfiguration = MetricsConfiguration'
{ _mcFilter :: !(Maybe MetricsFilter)
, _mcId :: !Text
} deriving (Eq, Read, Show, Data, Typeable, Generic)
metricsConfiguration
:: Text
-> MetricsConfiguration
metricsConfiguration pId_ =
MetricsConfiguration' {_mcFilter = Nothing, _mcId = pId_}
mcFilter :: Lens' MetricsConfiguration (Maybe MetricsFilter)
mcFilter = lens _mcFilter (\ s a -> s{_mcFilter = a})
mcId :: Lens' MetricsConfiguration Text
mcId = lens _mcId (\ s a -> s{_mcId = a})
instance FromXML MetricsConfiguration where
parseXML x
= MetricsConfiguration' <$>
(x .@? "Filter") <*> (x .@ "Id")
instance Hashable MetricsConfiguration where
instance NFData MetricsConfiguration where
instance ToXML MetricsConfiguration where
toXML MetricsConfiguration'{..}
= mconcat ["Filter" @= _mcFilter, "Id" @= _mcId]
data MetricsFilter = MetricsFilter'
{ _mfTag :: !(Maybe Tag)
, _mfPrefix :: !(Maybe Text)
, _mfAnd :: !(Maybe MetricsAndOperator)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
metricsFilter
:: MetricsFilter
metricsFilter =
MetricsFilter' {_mfTag = Nothing, _mfPrefix = Nothing, _mfAnd = Nothing}
mfTag :: Lens' MetricsFilter (Maybe Tag)
mfTag = lens _mfTag (\ s a -> s{_mfTag = a})
mfPrefix :: Lens' MetricsFilter (Maybe Text)
mfPrefix = lens _mfPrefix (\ s a -> s{_mfPrefix = a})
mfAnd :: Lens' MetricsFilter (Maybe MetricsAndOperator)
mfAnd = lens _mfAnd (\ s a -> s{_mfAnd = a})
instance FromXML MetricsFilter where
parseXML x
= MetricsFilter' <$>
(x .@? "Tag") <*> (x .@? "Prefix") <*> (x .@? "And")
instance Hashable MetricsFilter where
instance NFData MetricsFilter where
instance ToXML MetricsFilter where
toXML MetricsFilter'{..}
= mconcat
["Tag" @= _mfTag, "Prefix" @= _mfPrefix,
"And" @= _mfAnd]
data MultipartUpload = MultipartUpload'
{ _muInitiated :: !(Maybe RFC822)
, _muInitiator :: !(Maybe Initiator)
, _muOwner :: !(Maybe Owner)
, _muKey :: !(Maybe ObjectKey)
, _muStorageClass :: !(Maybe StorageClass)
, _muUploadId :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
multipartUpload
:: MultipartUpload
multipartUpload =
MultipartUpload'
{ _muInitiated = Nothing
, _muInitiator = Nothing
, _muOwner = Nothing
, _muKey = Nothing
, _muStorageClass = Nothing
, _muUploadId = Nothing
}
muInitiated :: Lens' MultipartUpload (Maybe UTCTime)
muInitiated = lens _muInitiated (\ s a -> s{_muInitiated = a}) . mapping _Time
muInitiator :: Lens' MultipartUpload (Maybe Initiator)
muInitiator = lens _muInitiator (\ s a -> s{_muInitiator = a})
muOwner :: Lens' MultipartUpload (Maybe Owner)
muOwner = lens _muOwner (\ s a -> s{_muOwner = a})
muKey :: Lens' MultipartUpload (Maybe ObjectKey)
muKey = lens _muKey (\ s a -> s{_muKey = a})
muStorageClass :: Lens' MultipartUpload (Maybe StorageClass)
muStorageClass = lens _muStorageClass (\ s a -> s{_muStorageClass = a})
muUploadId :: Lens' MultipartUpload (Maybe Text)
muUploadId = lens _muUploadId (\ s a -> s{_muUploadId = a})
instance FromXML MultipartUpload where
parseXML x
= MultipartUpload' <$>
(x .@? "Initiated") <*> (x .@? "Initiator") <*>
(x .@? "Owner")
<*> (x .@? "Key")
<*> (x .@? "StorageClass")
<*> (x .@? "UploadId")
instance Hashable MultipartUpload where
instance NFData MultipartUpload where
newtype NoncurrentVersionExpiration = NoncurrentVersionExpiration'
{ _nveNoncurrentDays :: Int
} deriving (Eq, Read, Show, Data, Typeable, Generic)
noncurrentVersionExpiration
:: Int
-> NoncurrentVersionExpiration
noncurrentVersionExpiration pNoncurrentDays_ =
NoncurrentVersionExpiration' {_nveNoncurrentDays = pNoncurrentDays_}
nveNoncurrentDays :: Lens' NoncurrentVersionExpiration Int
nveNoncurrentDays = lens _nveNoncurrentDays (\ s a -> s{_nveNoncurrentDays = a})
instance FromXML NoncurrentVersionExpiration where
parseXML x
= NoncurrentVersionExpiration' <$>
(x .@ "NoncurrentDays")
instance Hashable NoncurrentVersionExpiration where
instance NFData NoncurrentVersionExpiration where
instance ToXML NoncurrentVersionExpiration where
toXML NoncurrentVersionExpiration'{..}
= mconcat ["NoncurrentDays" @= _nveNoncurrentDays]
data NoncurrentVersionTransition = NoncurrentVersionTransition'
{ _nvtNoncurrentDays :: !Int
, _nvtStorageClass :: !TransitionStorageClass
} deriving (Eq, Read, Show, Data, Typeable, Generic)
noncurrentVersionTransition
:: Int
-> TransitionStorageClass
-> NoncurrentVersionTransition
noncurrentVersionTransition pNoncurrentDays_ pStorageClass_ =
NoncurrentVersionTransition'
{_nvtNoncurrentDays = pNoncurrentDays_, _nvtStorageClass = pStorageClass_}
nvtNoncurrentDays :: Lens' NoncurrentVersionTransition Int
nvtNoncurrentDays = lens _nvtNoncurrentDays (\ s a -> s{_nvtNoncurrentDays = a})
nvtStorageClass :: Lens' NoncurrentVersionTransition TransitionStorageClass
nvtStorageClass = lens _nvtStorageClass (\ s a -> s{_nvtStorageClass = a})
instance FromXML NoncurrentVersionTransition where
parseXML x
= NoncurrentVersionTransition' <$>
(x .@ "NoncurrentDays") <*> (x .@ "StorageClass")
instance Hashable NoncurrentVersionTransition where
instance NFData NoncurrentVersionTransition where
instance ToXML NoncurrentVersionTransition where
toXML NoncurrentVersionTransition'{..}
= mconcat
["NoncurrentDays" @= _nvtNoncurrentDays,
"StorageClass" @= _nvtStorageClass]
data NotificationConfiguration = NotificationConfiguration'
{ _ncQueueConfigurations :: !(Maybe [QueueConfiguration])
, _ncTopicConfigurations :: !(Maybe [TopicConfiguration])
, _ncLambdaFunctionConfigurations :: !(Maybe [LambdaFunctionConfiguration])
} deriving (Eq, Read, Show, Data, Typeable, Generic)
notificationConfiguration
:: NotificationConfiguration
notificationConfiguration =
NotificationConfiguration'
{ _ncQueueConfigurations = Nothing
, _ncTopicConfigurations = Nothing
, _ncLambdaFunctionConfigurations = Nothing
}
ncQueueConfigurations :: Lens' NotificationConfiguration [QueueConfiguration]
ncQueueConfigurations = lens _ncQueueConfigurations (\ s a -> s{_ncQueueConfigurations = a}) . _Default . _Coerce
ncTopicConfigurations :: Lens' NotificationConfiguration [TopicConfiguration]
ncTopicConfigurations = lens _ncTopicConfigurations (\ s a -> s{_ncTopicConfigurations = a}) . _Default . _Coerce
ncLambdaFunctionConfigurations :: Lens' NotificationConfiguration [LambdaFunctionConfiguration]
ncLambdaFunctionConfigurations = lens _ncLambdaFunctionConfigurations (\ s a -> s{_ncLambdaFunctionConfigurations = a}) . _Default . _Coerce
instance FromXML NotificationConfiguration where
parseXML x
= NotificationConfiguration' <$>
(may (parseXMLList "QueueConfiguration") x) <*>
(may (parseXMLList "TopicConfiguration") x)
<*>
(may (parseXMLList "CloudFunctionConfiguration") x)
instance Hashable NotificationConfiguration where
instance NFData NotificationConfiguration where
instance ToXML NotificationConfiguration where
toXML NotificationConfiguration'{..}
= mconcat
[toXML
(toXMLList "QueueConfiguration" <$>
_ncQueueConfigurations),
toXML
(toXMLList "TopicConfiguration" <$>
_ncTopicConfigurations),
toXML
(toXMLList "CloudFunctionConfiguration" <$>
_ncLambdaFunctionConfigurations)]
newtype NotificationConfigurationFilter = NotificationConfigurationFilter'
{ _ncfKey :: Maybe S3KeyFilter
} deriving (Eq, Read, Show, Data, Typeable, Generic)
notificationConfigurationFilter
:: NotificationConfigurationFilter
notificationConfigurationFilter =
NotificationConfigurationFilter' {_ncfKey = Nothing}
ncfKey :: Lens' NotificationConfigurationFilter (Maybe S3KeyFilter)
ncfKey = lens _ncfKey (\ s a -> s{_ncfKey = a})
instance FromXML NotificationConfigurationFilter
where
parseXML x
= NotificationConfigurationFilter' <$>
(x .@? "S3Key")
instance Hashable NotificationConfigurationFilter
where
instance NFData NotificationConfigurationFilter where
instance ToXML NotificationConfigurationFilter where
toXML NotificationConfigurationFilter'{..}
= mconcat ["S3Key" @= _ncfKey]
data Object = Object'
{ _oOwner :: !(Maybe Owner)
, _oETag :: !ETag
, _oSize :: !Int
, _oKey :: !ObjectKey
, _oStorageClass :: !ObjectStorageClass
, _oLastModified :: !RFC822
} deriving (Eq, Read, Show, Data, Typeable, Generic)
object'
:: ETag
-> Int
-> ObjectKey
-> ObjectStorageClass
-> UTCTime
-> Object
object' pETag_ pSize_ pKey_ pStorageClass_ pLastModified_ =
Object'
{ _oOwner = Nothing
, _oETag = pETag_
, _oSize = pSize_
, _oKey = pKey_
, _oStorageClass = pStorageClass_
, _oLastModified = _Time # pLastModified_
}
oOwner :: Lens' Object (Maybe Owner)
oOwner = lens _oOwner (\ s a -> s{_oOwner = a})
oETag :: Lens' Object ETag
oETag = lens _oETag (\ s a -> s{_oETag = a})
oSize :: Lens' Object Int
oSize = lens _oSize (\ s a -> s{_oSize = a})
oKey :: Lens' Object ObjectKey
oKey = lens _oKey (\ s a -> s{_oKey = a})
oStorageClass :: Lens' Object ObjectStorageClass
oStorageClass = lens _oStorageClass (\ s a -> s{_oStorageClass = a})
oLastModified :: Lens' Object UTCTime
oLastModified = lens _oLastModified (\ s a -> s{_oLastModified = a}) . _Time
instance FromXML Object where
parseXML x
= Object' <$>
(x .@? "Owner") <*> (x .@ "ETag") <*> (x .@ "Size")
<*> (x .@ "Key")
<*> (x .@ "StorageClass")
<*> (x .@ "LastModified")
instance Hashable Object where
instance NFData Object where
data ObjectIdentifier = ObjectIdentifier'
{ _oiVersionId :: !(Maybe ObjectVersionId)
, _oiKey :: !ObjectKey
} deriving (Eq, Read, Show, Data, Typeable, Generic)
objectIdentifier
:: ObjectKey
-> ObjectIdentifier
objectIdentifier pKey_ =
ObjectIdentifier' {_oiVersionId = Nothing, _oiKey = pKey_}
oiVersionId :: Lens' ObjectIdentifier (Maybe ObjectVersionId)
oiVersionId = lens _oiVersionId (\ s a -> s{_oiVersionId = a})
oiKey :: Lens' ObjectIdentifier ObjectKey
oiKey = lens _oiKey (\ s a -> s{_oiKey = a})
instance Hashable ObjectIdentifier where
instance NFData ObjectIdentifier where
instance ToXML ObjectIdentifier where
toXML ObjectIdentifier'{..}
= mconcat
["VersionId" @= _oiVersionId, "Key" @= _oiKey]
data ObjectVersion = ObjectVersion'
{ _ovETag :: !(Maybe ETag)
, _ovVersionId :: !(Maybe ObjectVersionId)
, _ovSize :: !(Maybe Int)
, _ovIsLatest :: !(Maybe Bool)
, _ovOwner :: !(Maybe Owner)
, _ovKey :: !(Maybe ObjectKey)
, _ovStorageClass :: !(Maybe ObjectVersionStorageClass)
, _ovLastModified :: !(Maybe RFC822)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
objectVersion
:: ObjectVersion
objectVersion =
ObjectVersion'
{ _ovETag = Nothing
, _ovVersionId = Nothing
, _ovSize = Nothing
, _ovIsLatest = Nothing
, _ovOwner = Nothing
, _ovKey = Nothing
, _ovStorageClass = Nothing
, _ovLastModified = Nothing
}
ovETag :: Lens' ObjectVersion (Maybe ETag)
ovETag = lens _ovETag (\ s a -> s{_ovETag = a})
ovVersionId :: Lens' ObjectVersion (Maybe ObjectVersionId)
ovVersionId = lens _ovVersionId (\ s a -> s{_ovVersionId = a})
ovSize :: Lens' ObjectVersion (Maybe Int)
ovSize = lens _ovSize (\ s a -> s{_ovSize = a})
ovIsLatest :: Lens' ObjectVersion (Maybe Bool)
ovIsLatest = lens _ovIsLatest (\ s a -> s{_ovIsLatest = a})
ovOwner :: Lens' ObjectVersion (Maybe Owner)
ovOwner = lens _ovOwner (\ s a -> s{_ovOwner = a})
ovKey :: Lens' ObjectVersion (Maybe ObjectKey)
ovKey = lens _ovKey (\ s a -> s{_ovKey = a})
ovStorageClass :: Lens' ObjectVersion (Maybe ObjectVersionStorageClass)
ovStorageClass = lens _ovStorageClass (\ s a -> s{_ovStorageClass = a})
ovLastModified :: Lens' ObjectVersion (Maybe UTCTime)
ovLastModified = lens _ovLastModified (\ s a -> s{_ovLastModified = a}) . mapping _Time
instance FromXML ObjectVersion where
parseXML x
= ObjectVersion' <$>
(x .@? "ETag") <*> (x .@? "VersionId") <*>
(x .@? "Size")
<*> (x .@? "IsLatest")
<*> (x .@? "Owner")
<*> (x .@? "Key")
<*> (x .@? "StorageClass")
<*> (x .@? "LastModified")
instance Hashable ObjectVersion where
instance NFData ObjectVersion where
newtype OutputLocation = OutputLocation'
{ _olS3 :: Maybe S3Location
} deriving (Eq, Show, Data, Typeable, Generic)
outputLocation
:: OutputLocation
outputLocation = OutputLocation' {_olS3 = Nothing}
olS3 :: Lens' OutputLocation (Maybe S3Location)
olS3 = lens _olS3 (\ s a -> s{_olS3 = a})
instance Hashable OutputLocation where
instance NFData OutputLocation where
instance ToXML OutputLocation where
toXML OutputLocation'{..} = mconcat ["S3" @= _olS3]
data OutputSerialization = OutputSerialization'
{ _osJSON :: !(Maybe JSONOutput)
, _osCSV :: !(Maybe CSVOutput)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
outputSerialization
:: OutputSerialization
outputSerialization = OutputSerialization' {_osJSON = Nothing, _osCSV = Nothing}
osJSON :: Lens' OutputSerialization (Maybe JSONOutput)
osJSON = lens _osJSON (\ s a -> s{_osJSON = a})
osCSV :: Lens' OutputSerialization (Maybe CSVOutput)
osCSV = lens _osCSV (\ s a -> s{_osCSV = a})
instance Hashable OutputSerialization where
instance NFData OutputSerialization where
instance ToXML OutputSerialization where
toXML OutputSerialization'{..}
= mconcat ["JSON" @= _osJSON, "CSV" @= _osCSV]
data Owner = Owner'
{ _oDisplayName :: !(Maybe Text)
, _oId :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
owner
:: Owner
owner = Owner' {_oDisplayName = Nothing, _oId = Nothing}
oDisplayName :: Lens' Owner (Maybe Text)
oDisplayName = lens _oDisplayName (\ s a -> s{_oDisplayName = a})
oId :: Lens' Owner (Maybe Text)
oId = lens _oId (\ s a -> s{_oId = a})
instance FromXML Owner where
parseXML x
= Owner' <$> (x .@? "DisplayName") <*> (x .@? "ID")
instance Hashable Owner where
instance NFData Owner where
instance ToXML Owner where
toXML Owner'{..}
= mconcat
["DisplayName" @= _oDisplayName, "ID" @= _oId]
data Part = Part'
{ _pETag :: !(Maybe ETag)
, _pSize :: !(Maybe Int)
, _pPartNumber :: !(Maybe Int)
, _pLastModified :: !(Maybe RFC822)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
part
:: Part
part =
Part'
{ _pETag = Nothing
, _pSize = Nothing
, _pPartNumber = Nothing
, _pLastModified = Nothing
}
pETag :: Lens' Part (Maybe ETag)
pETag = lens _pETag (\ s a -> s{_pETag = a})
pSize :: Lens' Part (Maybe Int)
pSize = lens _pSize (\ s a -> s{_pSize = a})
pPartNumber :: Lens' Part (Maybe Int)
pPartNumber = lens _pPartNumber (\ s a -> s{_pPartNumber = a})
pLastModified :: Lens' Part (Maybe UTCTime)
pLastModified = lens _pLastModified (\ s a -> s{_pLastModified = a}) . mapping _Time
instance FromXML Part where
parseXML x
= Part' <$>
(x .@? "ETag") <*> (x .@? "Size") <*>
(x .@? "PartNumber")
<*> (x .@? "LastModified")
instance Hashable Part where
instance NFData Part where
data Progress = Progress'
{ _pBytesReturned :: !(Maybe Integer)
, _pBytesScanned :: !(Maybe Integer)
, _pBytesProcessed :: !(Maybe Integer)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
progress
:: Progress
progress =
Progress'
{ _pBytesReturned = Nothing
, _pBytesScanned = Nothing
, _pBytesProcessed = Nothing
}
pBytesReturned :: Lens' Progress (Maybe Integer)
pBytesReturned = lens _pBytesReturned (\ s a -> s{_pBytesReturned = a})
pBytesScanned :: Lens' Progress (Maybe Integer)
pBytesScanned = lens _pBytesScanned (\ s a -> s{_pBytesScanned = a})
pBytesProcessed :: Lens' Progress (Maybe Integer)
pBytesProcessed = lens _pBytesProcessed (\ s a -> s{_pBytesProcessed = a})
instance FromXML Progress where
parseXML x
= Progress' <$>
(x .@? "BytesReturned") <*> (x .@? "BytesScanned")
<*> (x .@? "BytesProcessed")
instance Hashable Progress where
instance NFData Progress where
newtype ProgressEvent = ProgressEvent'
{ _peDetails :: Maybe Progress
} deriving (Eq, Read, Show, Data, Typeable, Generic)
progressEvent
:: ProgressEvent
progressEvent = ProgressEvent' {_peDetails = Nothing}
peDetails :: Lens' ProgressEvent (Maybe Progress)
peDetails = lens _peDetails (\ s a -> s{_peDetails = a})
instance FromXML ProgressEvent where
parseXML x = ProgressEvent' <$> (x .@? "Details")
instance Hashable ProgressEvent where
instance NFData ProgressEvent where
data QueueConfiguration = QueueConfiguration'
{ _qcId :: !(Maybe Text)
, _qcFilter :: !(Maybe NotificationConfigurationFilter)
, _qcQueueARN :: !Text
, _qcEvents :: ![Event]
} deriving (Eq, Read, Show, Data, Typeable, Generic)
queueConfiguration
:: Text
-> QueueConfiguration
queueConfiguration pQueueARN_ =
QueueConfiguration'
{ _qcId = Nothing
, _qcFilter = Nothing
, _qcQueueARN = pQueueARN_
, _qcEvents = mempty
}
qcId :: Lens' QueueConfiguration (Maybe Text)
qcId = lens _qcId (\ s a -> s{_qcId = a})
qcFilter :: Lens' QueueConfiguration (Maybe NotificationConfigurationFilter)
qcFilter = lens _qcFilter (\ s a -> s{_qcFilter = a})
qcQueueARN :: Lens' QueueConfiguration Text
qcQueueARN = lens _qcQueueARN (\ s a -> s{_qcQueueARN = a})
qcEvents :: Lens' QueueConfiguration [Event]
qcEvents = lens _qcEvents (\ s a -> s{_qcEvents = a}) . _Coerce
instance FromXML QueueConfiguration where
parseXML x
= QueueConfiguration' <$>
(x .@? "Id") <*> (x .@? "Filter") <*> (x .@ "Queue")
<*> (parseXMLList "Event" x)
instance Hashable QueueConfiguration where
instance NFData QueueConfiguration where
instance ToXML QueueConfiguration where
toXML QueueConfiguration'{..}
= mconcat
["Id" @= _qcId, "Filter" @= _qcFilter,
"Queue" @= _qcQueueARN, toXMLList "Event" _qcEvents]
newtype RecordsEvent = RecordsEvent'
{ _rePayload :: Maybe Base64
} deriving (Eq, Read, Show, Data, Typeable, Generic)
recordsEvent
:: RecordsEvent
recordsEvent = RecordsEvent' {_rePayload = Nothing}
rePayload :: Lens' RecordsEvent (Maybe ByteString)
rePayload = lens _rePayload (\ s a -> s{_rePayload = a}) . mapping _Base64
instance FromXML RecordsEvent where
parseXML x = RecordsEvent' <$> (x .@? "Payload")
instance Hashable RecordsEvent where
instance NFData RecordsEvent where
data Redirect = Redirect'
{ _rHostName :: !(Maybe Text)
, _rProtocol :: !(Maybe Protocol)
, _rHTTPRedirectCode :: !(Maybe Text)
, _rReplaceKeyWith :: !(Maybe Text)
, _rReplaceKeyPrefixWith :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
redirect
:: Redirect
redirect =
Redirect'
{ _rHostName = Nothing
, _rProtocol = Nothing
, _rHTTPRedirectCode = Nothing
, _rReplaceKeyWith = Nothing
, _rReplaceKeyPrefixWith = Nothing
}
rHostName :: Lens' Redirect (Maybe Text)
rHostName = lens _rHostName (\ s a -> s{_rHostName = a})
rProtocol :: Lens' Redirect (Maybe Protocol)
rProtocol = lens _rProtocol (\ s a -> s{_rProtocol = a})
rHTTPRedirectCode :: Lens' Redirect (Maybe Text)
rHTTPRedirectCode = lens _rHTTPRedirectCode (\ s a -> s{_rHTTPRedirectCode = a})
rReplaceKeyWith :: Lens' Redirect (Maybe Text)
rReplaceKeyWith = lens _rReplaceKeyWith (\ s a -> s{_rReplaceKeyWith = a})
rReplaceKeyPrefixWith :: Lens' Redirect (Maybe Text)
rReplaceKeyPrefixWith = lens _rReplaceKeyPrefixWith (\ s a -> s{_rReplaceKeyPrefixWith = a})
instance FromXML Redirect where
parseXML x
= Redirect' <$>
(x .@? "HostName") <*> (x .@? "Protocol") <*>
(x .@? "HttpRedirectCode")
<*> (x .@? "ReplaceKeyWith")
<*> (x .@? "ReplaceKeyPrefixWith")
instance Hashable Redirect where
instance NFData Redirect where
instance ToXML Redirect where
toXML Redirect'{..}
= mconcat
["HostName" @= _rHostName, "Protocol" @= _rProtocol,
"HttpRedirectCode" @= _rHTTPRedirectCode,
"ReplaceKeyWith" @= _rReplaceKeyWith,
"ReplaceKeyPrefixWith" @= _rReplaceKeyPrefixWith]
data RedirectAllRequestsTo = RedirectAllRequestsTo'
{ _rartProtocol :: !(Maybe Protocol)
, _rartHostName :: !Text
} deriving (Eq, Read, Show, Data, Typeable, Generic)
redirectAllRequestsTo
:: Text
-> RedirectAllRequestsTo
redirectAllRequestsTo pHostName_ =
RedirectAllRequestsTo' {_rartProtocol = Nothing, _rartHostName = pHostName_}
rartProtocol :: Lens' RedirectAllRequestsTo (Maybe Protocol)
rartProtocol = lens _rartProtocol (\ s a -> s{_rartProtocol = a})
rartHostName :: Lens' RedirectAllRequestsTo Text
rartHostName = lens _rartHostName (\ s a -> s{_rartHostName = a})
instance FromXML RedirectAllRequestsTo where
parseXML x
= RedirectAllRequestsTo' <$>
(x .@? "Protocol") <*> (x .@ "HostName")
instance Hashable RedirectAllRequestsTo where
instance NFData RedirectAllRequestsTo where
instance ToXML RedirectAllRequestsTo where
toXML RedirectAllRequestsTo'{..}
= mconcat
["Protocol" @= _rartProtocol,
"HostName" @= _rartHostName]
data ReplicationConfiguration = ReplicationConfiguration'
{ _rcRole :: !Text
, _rcRules :: ![ReplicationRule]
} deriving (Eq, Read, Show, Data, Typeable, Generic)
replicationConfiguration
:: Text
-> ReplicationConfiguration
replicationConfiguration pRole_ =
ReplicationConfiguration' {_rcRole = pRole_, _rcRules = mempty}
rcRole :: Lens' ReplicationConfiguration Text
rcRole = lens _rcRole (\ s a -> s{_rcRole = a})
rcRules :: Lens' ReplicationConfiguration [ReplicationRule]
rcRules = lens _rcRules (\ s a -> s{_rcRules = a}) . _Coerce
instance FromXML ReplicationConfiguration where
parseXML x
= ReplicationConfiguration' <$>
(x .@ "Role") <*> (parseXMLList "Rule" x)
instance Hashable ReplicationConfiguration where
instance NFData ReplicationConfiguration where
instance ToXML ReplicationConfiguration where
toXML ReplicationConfiguration'{..}
= mconcat
["Role" @= _rcRole, toXMLList "Rule" _rcRules]
data ReplicationRule = ReplicationRule'
{ _rrId :: !(Maybe Text)
, _rrSourceSelectionCriteria :: !(Maybe SourceSelectionCriteria)
, _rrPrefix :: !Text
, _rrStatus :: !ReplicationRuleStatus
, _rrDestination :: !Destination
} deriving (Eq, Read, Show, Data, Typeable, Generic)
replicationRule
:: Text
-> ReplicationRuleStatus
-> Destination
-> ReplicationRule
replicationRule pPrefix_ pStatus_ pDestination_ =
ReplicationRule'
{ _rrId = Nothing
, _rrSourceSelectionCriteria = Nothing
, _rrPrefix = pPrefix_
, _rrStatus = pStatus_
, _rrDestination = pDestination_
}
rrId :: Lens' ReplicationRule (Maybe Text)
rrId = lens _rrId (\ s a -> s{_rrId = a})
rrSourceSelectionCriteria :: Lens' ReplicationRule (Maybe SourceSelectionCriteria)
rrSourceSelectionCriteria = lens _rrSourceSelectionCriteria (\ s a -> s{_rrSourceSelectionCriteria = a})
rrPrefix :: Lens' ReplicationRule Text
rrPrefix = lens _rrPrefix (\ s a -> s{_rrPrefix = a})
rrStatus :: Lens' ReplicationRule ReplicationRuleStatus
rrStatus = lens _rrStatus (\ s a -> s{_rrStatus = a})
rrDestination :: Lens' ReplicationRule Destination
rrDestination = lens _rrDestination (\ s a -> s{_rrDestination = a})
instance FromXML ReplicationRule where
parseXML x
= ReplicationRule' <$>
(x .@? "ID") <*> (x .@? "SourceSelectionCriteria")
<*> (x .@ "Prefix")
<*> (x .@ "Status")
<*> (x .@ "Destination")
instance Hashable ReplicationRule where
instance NFData ReplicationRule where
instance ToXML ReplicationRule where
toXML ReplicationRule'{..}
= mconcat
["ID" @= _rrId,
"SourceSelectionCriteria" @=
_rrSourceSelectionCriteria,
"Prefix" @= _rrPrefix, "Status" @= _rrStatus,
"Destination" @= _rrDestination]
newtype RequestPaymentConfiguration = RequestPaymentConfiguration'
{ _rpcPayer :: Payer
} deriving (Eq, Read, Show, Data, Typeable, Generic)
requestPaymentConfiguration
:: Payer
-> RequestPaymentConfiguration
requestPaymentConfiguration pPayer_ =
RequestPaymentConfiguration' {_rpcPayer = pPayer_}
rpcPayer :: Lens' RequestPaymentConfiguration Payer
rpcPayer = lens _rpcPayer (\ s a -> s{_rpcPayer = a})
instance Hashable RequestPaymentConfiguration where
instance NFData RequestPaymentConfiguration where
instance ToXML RequestPaymentConfiguration where
toXML RequestPaymentConfiguration'{..}
= mconcat ["Payer" @= _rpcPayer]
newtype RequestProgress = RequestProgress'
{ _rpEnabled :: Maybe Bool
} deriving (Eq, Read, Show, Data, Typeable, Generic)
requestProgress
:: RequestProgress
requestProgress = RequestProgress' {_rpEnabled = Nothing}
rpEnabled :: Lens' RequestProgress (Maybe Bool)
rpEnabled = lens _rpEnabled (\ s a -> s{_rpEnabled = a})
instance Hashable RequestProgress where
instance NFData RequestProgress where
instance ToXML RequestProgress where
toXML RequestProgress'{..}
= mconcat ["Enabled" @= _rpEnabled]
data RestoreRequest = RestoreRequest'
{ _rrDays :: !(Maybe Int)
, _rrSelectParameters :: !(Maybe SelectParameters)
, _rrOutputLocation :: !(Maybe OutputLocation)
, _rrTier :: !(Maybe Tier)
, _rrGlacierJobParameters :: !(Maybe GlacierJobParameters)
, _rrType :: !(Maybe RestoreRequestType)
, _rrDescription :: !(Maybe Text)
} deriving (Eq, Show, Data, Typeable, Generic)
restoreRequest
:: RestoreRequest
restoreRequest =
RestoreRequest'
{ _rrDays = Nothing
, _rrSelectParameters = Nothing
, _rrOutputLocation = Nothing
, _rrTier = Nothing
, _rrGlacierJobParameters = Nothing
, _rrType = Nothing
, _rrDescription = Nothing
}
rrDays :: Lens' RestoreRequest (Maybe Int)
rrDays = lens _rrDays (\ s a -> s{_rrDays = a})
rrSelectParameters :: Lens' RestoreRequest (Maybe SelectParameters)
rrSelectParameters = lens _rrSelectParameters (\ s a -> s{_rrSelectParameters = a})
rrOutputLocation :: Lens' RestoreRequest (Maybe OutputLocation)
rrOutputLocation = lens _rrOutputLocation (\ s a -> s{_rrOutputLocation = a})
rrTier :: Lens' RestoreRequest (Maybe Tier)
rrTier = lens _rrTier (\ s a -> s{_rrTier = a})
rrGlacierJobParameters :: Lens' RestoreRequest (Maybe GlacierJobParameters)
rrGlacierJobParameters = lens _rrGlacierJobParameters (\ s a -> s{_rrGlacierJobParameters = a})
rrType :: Lens' RestoreRequest (Maybe RestoreRequestType)
rrType = lens _rrType (\ s a -> s{_rrType = a})
rrDescription :: Lens' RestoreRequest (Maybe Text)
rrDescription = lens _rrDescription (\ s a -> s{_rrDescription = a})
instance Hashable RestoreRequest where
instance NFData RestoreRequest where
instance ToXML RestoreRequest where
toXML RestoreRequest'{..}
= mconcat
["Days" @= _rrDays,
"SelectParameters" @= _rrSelectParameters,
"OutputLocation" @= _rrOutputLocation,
"Tier" @= _rrTier,
"GlacierJobParameters" @= _rrGlacierJobParameters,
"Type" @= _rrType, "Description" @= _rrDescription]
data RoutingRule = RoutingRule'
{ _rrCondition :: !(Maybe Condition)
, _rrRedirect :: !Redirect
} deriving (Eq, Read, Show, Data, Typeable, Generic)
routingRule
:: Redirect
-> RoutingRule
routingRule pRedirect_ =
RoutingRule' {_rrCondition = Nothing, _rrRedirect = pRedirect_}
rrCondition :: Lens' RoutingRule (Maybe Condition)
rrCondition = lens _rrCondition (\ s a -> s{_rrCondition = a})
rrRedirect :: Lens' RoutingRule Redirect
rrRedirect = lens _rrRedirect (\ s a -> s{_rrRedirect = a})
instance FromXML RoutingRule where
parseXML x
= RoutingRule' <$>
(x .@? "Condition") <*> (x .@ "Redirect")
instance Hashable RoutingRule where
instance NFData RoutingRule where
instance ToXML RoutingRule where
toXML RoutingRule'{..}
= mconcat
["Condition" @= _rrCondition,
"Redirect" @= _rrRedirect]
newtype S3KeyFilter = S3KeyFilter'
{ _skfFilterRules :: Maybe [FilterRule]
} deriving (Eq, Read, Show, Data, Typeable, Generic)
s3KeyFilter
:: S3KeyFilter
s3KeyFilter = S3KeyFilter' {_skfFilterRules = Nothing}
skfFilterRules :: Lens' S3KeyFilter [FilterRule]
skfFilterRules = lens _skfFilterRules (\ s a -> s{_skfFilterRules = a}) . _Default . _Coerce
instance FromXML S3KeyFilter where
parseXML x
= S3KeyFilter' <$>
(may (parseXMLList "FilterRule") x)
instance Hashable S3KeyFilter where
instance NFData S3KeyFilter where
instance ToXML S3KeyFilter where
toXML S3KeyFilter'{..}
= mconcat
[toXML (toXMLList "FilterRule" <$> _skfFilterRules)]
data S3Location = S3Location'
{ _slCannedACL :: !(Maybe ObjectCannedACL)
, _slAccessControlList :: !(Maybe [Grant])
, _slUserMetadata :: !(Maybe [MetadataEntry])
, _slEncryption :: !(Maybe Encryption)
, _slStorageClass :: !(Maybe StorageClass)
, _slTagging :: !(Maybe Tagging)
, _slBucketName :: !BucketName
, _slPrefix :: !Text
} deriving (Eq, Show, Data, Typeable, Generic)
s3Location
:: BucketName
-> Text
-> S3Location
s3Location pBucketName_ pPrefix_ =
S3Location'
{ _slCannedACL = Nothing
, _slAccessControlList = Nothing
, _slUserMetadata = Nothing
, _slEncryption = Nothing
, _slStorageClass = Nothing
, _slTagging = Nothing
, _slBucketName = pBucketName_
, _slPrefix = pPrefix_
}
slCannedACL :: Lens' S3Location (Maybe ObjectCannedACL)
slCannedACL = lens _slCannedACL (\ s a -> s{_slCannedACL = a})
slAccessControlList :: Lens' S3Location [Grant]
slAccessControlList = lens _slAccessControlList (\ s a -> s{_slAccessControlList = a}) . _Default . _Coerce
slUserMetadata :: Lens' S3Location [MetadataEntry]
slUserMetadata = lens _slUserMetadata (\ s a -> s{_slUserMetadata = a}) . _Default . _Coerce
slEncryption :: Lens' S3Location (Maybe Encryption)
slEncryption = lens _slEncryption (\ s a -> s{_slEncryption = a})
slStorageClass :: Lens' S3Location (Maybe StorageClass)
slStorageClass = lens _slStorageClass (\ s a -> s{_slStorageClass = a})
slTagging :: Lens' S3Location (Maybe Tagging)
slTagging = lens _slTagging (\ s a -> s{_slTagging = a})
slBucketName :: Lens' S3Location BucketName
slBucketName = lens _slBucketName (\ s a -> s{_slBucketName = a})
slPrefix :: Lens' S3Location Text
slPrefix = lens _slPrefix (\ s a -> s{_slPrefix = a})
instance Hashable S3Location where
instance NFData S3Location where
instance ToXML S3Location where
toXML S3Location'{..}
= mconcat
["CannedACL" @= _slCannedACL,
"AccessControlList" @=
toXML (toXMLList "Grant" <$> _slAccessControlList),
"UserMetadata" @=
toXML
(toXMLList "MetadataEntry" <$> _slUserMetadata),
"Encryption" @= _slEncryption,
"StorageClass" @= _slStorageClass,
"Tagging" @= _slTagging,
"BucketName" @= _slBucketName, "Prefix" @= _slPrefix]
data S3ServiceError = S3ServiceError'
{ _sseVersionId :: !(Maybe ObjectVersionId)
, _sseKey :: !(Maybe ObjectKey)
, _sseCode :: !(Maybe Text)
, _sseMessage :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
s3ServiceError
:: S3ServiceError
s3ServiceError =
S3ServiceError'
{ _sseVersionId = Nothing
, _sseKey = Nothing
, _sseCode = Nothing
, _sseMessage = Nothing
}
sseVersionId :: Lens' S3ServiceError (Maybe ObjectVersionId)
sseVersionId = lens _sseVersionId (\ s a -> s{_sseVersionId = a})
sseKey :: Lens' S3ServiceError (Maybe ObjectKey)
sseKey = lens _sseKey (\ s a -> s{_sseKey = a})
sseCode :: Lens' S3ServiceError (Maybe Text)
sseCode = lens _sseCode (\ s a -> s{_sseCode = a})
sseMessage :: Lens' S3ServiceError (Maybe Text)
sseMessage = lens _sseMessage (\ s a -> s{_sseMessage = a})
instance FromXML S3ServiceError where
parseXML x
= S3ServiceError' <$>
(x .@? "VersionId") <*> (x .@? "Key") <*>
(x .@? "Code")
<*> (x .@? "Message")
instance Hashable S3ServiceError where
instance NFData S3ServiceError where
newtype SSEKMS = SSEKMS'
{ _ssekKeyId :: Sensitive Text
} deriving (Eq, Show, Data, Typeable, Generic)
sSEKMS
:: Text
-> SSEKMS
sSEKMS pKeyId_ = SSEKMS' {_ssekKeyId = _Sensitive # pKeyId_}
ssekKeyId :: Lens' SSEKMS Text
ssekKeyId = lens _ssekKeyId (\ s a -> s{_ssekKeyId = a}) . _Sensitive
instance FromXML SSEKMS where
parseXML x = SSEKMS' <$> (x .@ "KeyId")
instance Hashable SSEKMS where
instance NFData SSEKMS where
instance ToXML SSEKMS where
toXML SSEKMS'{..} = mconcat ["KeyId" @= _ssekKeyId]
data SSES3 =
SSES3'
deriving (Eq, Read, Show, Data, Typeable, Generic)
sSES3
:: SSES3
sSES3 = SSES3'
instance FromXML SSES3 where
parseXML = const (pure SSES3')
instance Hashable SSES3 where
instance NFData SSES3 where
instance ToXML SSES3 where
toXML = const mempty
data SelectObjectContentEventStream = SelectObjectContentEventStream'
{ _socesProgress :: !(Maybe ProgressEvent)
, _socesRecords :: !(Maybe RecordsEvent)
, _socesCont :: !(Maybe ContinuationEvent)
, _socesStats :: !(Maybe StatsEvent)
, _socesEnd :: !(Maybe EndEvent)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
selectObjectContentEventStream
:: SelectObjectContentEventStream
selectObjectContentEventStream =
SelectObjectContentEventStream'
{ _socesProgress = Nothing
, _socesRecords = Nothing
, _socesCont = Nothing
, _socesStats = Nothing
, _socesEnd = Nothing
}
socesProgress :: Lens' SelectObjectContentEventStream (Maybe ProgressEvent)
socesProgress = lens _socesProgress (\ s a -> s{_socesProgress = a})
socesRecords :: Lens' SelectObjectContentEventStream (Maybe RecordsEvent)
socesRecords = lens _socesRecords (\ s a -> s{_socesRecords = a})
socesCont :: Lens' SelectObjectContentEventStream (Maybe ContinuationEvent)
socesCont = lens _socesCont (\ s a -> s{_socesCont = a})
socesStats :: Lens' SelectObjectContentEventStream (Maybe StatsEvent)
socesStats = lens _socesStats (\ s a -> s{_socesStats = a})
socesEnd :: Lens' SelectObjectContentEventStream (Maybe EndEvent)
socesEnd = lens _socesEnd (\ s a -> s{_socesEnd = a})
instance FromXML SelectObjectContentEventStream where
parseXML x
= SelectObjectContentEventStream' <$>
(x .@? "Progress") <*> (x .@? "Records") <*>
(x .@? "Cont")
<*> (x .@? "Stats")
<*> (x .@? "End")
instance Hashable SelectObjectContentEventStream
where
instance NFData SelectObjectContentEventStream where
data SelectParameters = SelectParameters'
{ _spInputSerialization :: !InputSerialization
, _spExpressionType :: !ExpressionType
, _spExpression :: !Text
, _spOutputSerialization :: !OutputSerialization
} deriving (Eq, Read, Show, Data, Typeable, Generic)
selectParameters
:: InputSerialization
-> ExpressionType
-> Text
-> OutputSerialization
-> SelectParameters
selectParameters pInputSerialization_ pExpressionType_ pExpression_ pOutputSerialization_ =
SelectParameters'
{ _spInputSerialization = pInputSerialization_
, _spExpressionType = pExpressionType_
, _spExpression = pExpression_
, _spOutputSerialization = pOutputSerialization_
}
spInputSerialization :: Lens' SelectParameters InputSerialization
spInputSerialization = lens _spInputSerialization (\ s a -> s{_spInputSerialization = a})
spExpressionType :: Lens' SelectParameters ExpressionType
spExpressionType = lens _spExpressionType (\ s a -> s{_spExpressionType = a})
spExpression :: Lens' SelectParameters Text
spExpression = lens _spExpression (\ s a -> s{_spExpression = a})
spOutputSerialization :: Lens' SelectParameters OutputSerialization
spOutputSerialization = lens _spOutputSerialization (\ s a -> s{_spOutputSerialization = a})
instance Hashable SelectParameters where
instance NFData SelectParameters where
instance ToXML SelectParameters where
toXML SelectParameters'{..}
= mconcat
["InputSerialization" @= _spInputSerialization,
"ExpressionType" @= _spExpressionType,
"Expression" @= _spExpression,
"OutputSerialization" @= _spOutputSerialization]
data ServerSideEncryptionByDefault = ServerSideEncryptionByDefault'
{ _ssebdKMSMasterKeyId :: !(Maybe (Sensitive Text))
, _ssebdSSEAlgorithm :: !ServerSideEncryption
} deriving (Eq, Show, Data, Typeable, Generic)
serverSideEncryptionByDefault
:: ServerSideEncryption
-> ServerSideEncryptionByDefault
serverSideEncryptionByDefault pSSEAlgorithm_ =
ServerSideEncryptionByDefault'
{_ssebdKMSMasterKeyId = Nothing, _ssebdSSEAlgorithm = pSSEAlgorithm_}
ssebdKMSMasterKeyId :: Lens' ServerSideEncryptionByDefault (Maybe Text)
ssebdKMSMasterKeyId = lens _ssebdKMSMasterKeyId (\ s a -> s{_ssebdKMSMasterKeyId = a}) . mapping _Sensitive
ssebdSSEAlgorithm :: Lens' ServerSideEncryptionByDefault ServerSideEncryption
ssebdSSEAlgorithm = lens _ssebdSSEAlgorithm (\ s a -> s{_ssebdSSEAlgorithm = a})
instance FromXML ServerSideEncryptionByDefault where
parseXML x
= ServerSideEncryptionByDefault' <$>
(x .@? "KMSMasterKeyID") <*> (x .@ "SSEAlgorithm")
instance Hashable ServerSideEncryptionByDefault where
instance NFData ServerSideEncryptionByDefault where
instance ToXML ServerSideEncryptionByDefault where
toXML ServerSideEncryptionByDefault'{..}
= mconcat
["KMSMasterKeyID" @= _ssebdKMSMasterKeyId,
"SSEAlgorithm" @= _ssebdSSEAlgorithm]
newtype ServerSideEncryptionConfiguration = ServerSideEncryptionConfiguration'
{ _ssecRules :: [ServerSideEncryptionRule]
} deriving (Eq, Show, Data, Typeable, Generic)
serverSideEncryptionConfiguration
:: ServerSideEncryptionConfiguration
serverSideEncryptionConfiguration =
ServerSideEncryptionConfiguration' {_ssecRules = mempty}
ssecRules :: Lens' ServerSideEncryptionConfiguration [ServerSideEncryptionRule]
ssecRules = lens _ssecRules (\ s a -> s{_ssecRules = a}) . _Coerce
instance FromXML ServerSideEncryptionConfiguration
where
parseXML x
= ServerSideEncryptionConfiguration' <$>
(parseXMLList "Rule" x)
instance Hashable ServerSideEncryptionConfiguration
where
instance NFData ServerSideEncryptionConfiguration
where
instance ToXML ServerSideEncryptionConfiguration
where
toXML ServerSideEncryptionConfiguration'{..}
= mconcat [toXMLList "Rule" _ssecRules]
newtype ServerSideEncryptionRule = ServerSideEncryptionRule'
{ _sserApplyServerSideEncryptionByDefault :: Maybe ServerSideEncryptionByDefault
} deriving (Eq, Show, Data, Typeable, Generic)
serverSideEncryptionRule
:: ServerSideEncryptionRule
serverSideEncryptionRule =
ServerSideEncryptionRule' {_sserApplyServerSideEncryptionByDefault = Nothing}
sserApplyServerSideEncryptionByDefault :: Lens' ServerSideEncryptionRule (Maybe ServerSideEncryptionByDefault)
sserApplyServerSideEncryptionByDefault = lens _sserApplyServerSideEncryptionByDefault (\ s a -> s{_sserApplyServerSideEncryptionByDefault = a})
instance FromXML ServerSideEncryptionRule where
parseXML x
= ServerSideEncryptionRule' <$>
(x .@? "ApplyServerSideEncryptionByDefault")
instance Hashable ServerSideEncryptionRule where
instance NFData ServerSideEncryptionRule where
instance ToXML ServerSideEncryptionRule where
toXML ServerSideEncryptionRule'{..}
= mconcat
["ApplyServerSideEncryptionByDefault" @=
_sserApplyServerSideEncryptionByDefault]
newtype SourceSelectionCriteria = SourceSelectionCriteria'
{ _sscSseKMSEncryptedObjects :: Maybe SseKMSEncryptedObjects
} deriving (Eq, Read, Show, Data, Typeable, Generic)
sourceSelectionCriteria
:: SourceSelectionCriteria
sourceSelectionCriteria =
SourceSelectionCriteria' {_sscSseKMSEncryptedObjects = Nothing}
sscSseKMSEncryptedObjects :: Lens' SourceSelectionCriteria (Maybe SseKMSEncryptedObjects)
sscSseKMSEncryptedObjects = lens _sscSseKMSEncryptedObjects (\ s a -> s{_sscSseKMSEncryptedObjects = a})
instance FromXML SourceSelectionCriteria where
parseXML x
= SourceSelectionCriteria' <$>
(x .@? "SseKmsEncryptedObjects")
instance Hashable SourceSelectionCriteria where
instance NFData SourceSelectionCriteria where
instance ToXML SourceSelectionCriteria where
toXML SourceSelectionCriteria'{..}
= mconcat
["SseKmsEncryptedObjects" @=
_sscSseKMSEncryptedObjects]
newtype SseKMSEncryptedObjects = SseKMSEncryptedObjects'
{ _skeoStatus :: SseKMSEncryptedObjectsStatus
} deriving (Eq, Read, Show, Data, Typeable, Generic)
sseKMSEncryptedObjects
:: SseKMSEncryptedObjectsStatus
-> SseKMSEncryptedObjects
sseKMSEncryptedObjects pStatus_ =
SseKMSEncryptedObjects' {_skeoStatus = pStatus_}
skeoStatus :: Lens' SseKMSEncryptedObjects SseKMSEncryptedObjectsStatus
skeoStatus = lens _skeoStatus (\ s a -> s{_skeoStatus = a})
instance FromXML SseKMSEncryptedObjects where
parseXML x
= SseKMSEncryptedObjects' <$> (x .@ "Status")
instance Hashable SseKMSEncryptedObjects where
instance NFData SseKMSEncryptedObjects where
instance ToXML SseKMSEncryptedObjects where
toXML SseKMSEncryptedObjects'{..}
= mconcat ["Status" @= _skeoStatus]
data Stats = Stats'
{ _sBytesReturned :: !(Maybe Integer)
, _sBytesScanned :: !(Maybe Integer)
, _sBytesProcessed :: !(Maybe Integer)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
stats
:: Stats
stats =
Stats'
{ _sBytesReturned = Nothing
, _sBytesScanned = Nothing
, _sBytesProcessed = Nothing
}
sBytesReturned :: Lens' Stats (Maybe Integer)
sBytesReturned = lens _sBytesReturned (\ s a -> s{_sBytesReturned = a})
sBytesScanned :: Lens' Stats (Maybe Integer)
sBytesScanned = lens _sBytesScanned (\ s a -> s{_sBytesScanned = a})
sBytesProcessed :: Lens' Stats (Maybe Integer)
sBytesProcessed = lens _sBytesProcessed (\ s a -> s{_sBytesProcessed = a})
instance FromXML Stats where
parseXML x
= Stats' <$>
(x .@? "BytesReturned") <*> (x .@? "BytesScanned")
<*> (x .@? "BytesProcessed")
instance Hashable Stats where
instance NFData Stats where
newtype StatsEvent = StatsEvent'
{ _seDetails :: Maybe Stats
} deriving (Eq, Read, Show, Data, Typeable, Generic)
statsEvent
:: StatsEvent
statsEvent = StatsEvent' {_seDetails = Nothing}
seDetails :: Lens' StatsEvent (Maybe Stats)
seDetails = lens _seDetails (\ s a -> s{_seDetails = a})
instance FromXML StatsEvent where
parseXML x = StatsEvent' <$> (x .@? "Details")
instance Hashable StatsEvent where
instance NFData StatsEvent where
newtype StorageClassAnalysis = StorageClassAnalysis'
{ _scaDataExport :: Maybe StorageClassAnalysisDataExport
} deriving (Eq, Read, Show, Data, Typeable, Generic)
storageClassAnalysis
:: StorageClassAnalysis
storageClassAnalysis = StorageClassAnalysis' {_scaDataExport = Nothing}
scaDataExport :: Lens' StorageClassAnalysis (Maybe StorageClassAnalysisDataExport)
scaDataExport = lens _scaDataExport (\ s a -> s{_scaDataExport = a})
instance FromXML StorageClassAnalysis where
parseXML x
= StorageClassAnalysis' <$> (x .@? "DataExport")
instance Hashable StorageClassAnalysis where
instance NFData StorageClassAnalysis where
instance ToXML StorageClassAnalysis where
toXML StorageClassAnalysis'{..}
= mconcat ["DataExport" @= _scaDataExport]
data StorageClassAnalysisDataExport = StorageClassAnalysisDataExport'
{ _scadeOutputSchemaVersion :: !StorageClassAnalysisSchemaVersion
, _scadeDestination :: !AnalyticsExportDestination
} deriving (Eq, Read, Show, Data, Typeable, Generic)
storageClassAnalysisDataExport
:: StorageClassAnalysisSchemaVersion
-> AnalyticsExportDestination
-> StorageClassAnalysisDataExport
storageClassAnalysisDataExport pOutputSchemaVersion_ pDestination_ =
StorageClassAnalysisDataExport'
{ _scadeOutputSchemaVersion = pOutputSchemaVersion_
, _scadeDestination = pDestination_
}
scadeOutputSchemaVersion :: Lens' StorageClassAnalysisDataExport StorageClassAnalysisSchemaVersion
scadeOutputSchemaVersion = lens _scadeOutputSchemaVersion (\ s a -> s{_scadeOutputSchemaVersion = a})
scadeDestination :: Lens' StorageClassAnalysisDataExport AnalyticsExportDestination
scadeDestination = lens _scadeDestination (\ s a -> s{_scadeDestination = a})
instance FromXML StorageClassAnalysisDataExport where
parseXML x
= StorageClassAnalysisDataExport' <$>
(x .@ "OutputSchemaVersion") <*> (x .@ "Destination")
instance Hashable StorageClassAnalysisDataExport
where
instance NFData StorageClassAnalysisDataExport where
instance ToXML StorageClassAnalysisDataExport where
toXML StorageClassAnalysisDataExport'{..}
= mconcat
["OutputSchemaVersion" @= _scadeOutputSchemaVersion,
"Destination" @= _scadeDestination]
data Tag = Tag'
{ _tagKey :: !ObjectKey
, _tagValue :: !Text
} deriving (Eq, Read, Show, Data, Typeable, Generic)
tag
:: ObjectKey
-> Text
-> Tag
tag pKey_ pValue_ = Tag' {_tagKey = pKey_, _tagValue = pValue_}
tagKey :: Lens' Tag ObjectKey
tagKey = lens _tagKey (\ s a -> s{_tagKey = a})
tagValue :: Lens' Tag Text
tagValue = lens _tagValue (\ s a -> s{_tagValue = a})
instance FromXML Tag where
parseXML x = Tag' <$> (x .@ "Key") <*> (x .@ "Value")
instance Hashable Tag where
instance NFData Tag where
instance ToXML Tag where
toXML Tag'{..}
= mconcat ["Key" @= _tagKey, "Value" @= _tagValue]
newtype Tagging = Tagging'
{ _tTagSet :: [Tag]
} deriving (Eq, Read, Show, Data, Typeable, Generic)
tagging
:: Tagging
tagging = Tagging' {_tTagSet = mempty}
tTagSet :: Lens' Tagging [Tag]
tTagSet = lens _tTagSet (\ s a -> s{_tTagSet = a}) . _Coerce
instance Hashable Tagging where
instance NFData Tagging where
instance ToXML Tagging where
toXML Tagging'{..}
= mconcat ["TagSet" @= toXMLList "Tag" _tTagSet]
data TargetGrant = TargetGrant'
{ _tgPermission :: !(Maybe BucketLogsPermission)
, _tgGrantee :: !(Maybe Grantee)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
targetGrant
:: TargetGrant
targetGrant = TargetGrant' {_tgPermission = Nothing, _tgGrantee = Nothing}
tgPermission :: Lens' TargetGrant (Maybe BucketLogsPermission)
tgPermission = lens _tgPermission (\ s a -> s{_tgPermission = a})
tgGrantee :: Lens' TargetGrant (Maybe Grantee)
tgGrantee = lens _tgGrantee (\ s a -> s{_tgGrantee = a})
instance FromXML TargetGrant where
parseXML x
= TargetGrant' <$>
(x .@? "Permission") <*> (x .@? "Grantee")
instance Hashable TargetGrant where
instance NFData TargetGrant where
instance ToXML TargetGrant where
toXML TargetGrant'{..}
= mconcat
["Permission" @= _tgPermission,
"Grantee" @= _tgGrantee]
data TopicConfiguration = TopicConfiguration'
{ _tcId :: !(Maybe Text)
, _tcFilter :: !(Maybe NotificationConfigurationFilter)
, _tcTopicARN :: !Text
, _tcEvents :: ![Event]
} deriving (Eq, Read, Show, Data, Typeable, Generic)
topicConfiguration
:: Text
-> TopicConfiguration
topicConfiguration pTopicARN_ =
TopicConfiguration'
{ _tcId = Nothing
, _tcFilter = Nothing
, _tcTopicARN = pTopicARN_
, _tcEvents = mempty
}
tcId :: Lens' TopicConfiguration (Maybe Text)
tcId = lens _tcId (\ s a -> s{_tcId = a})
tcFilter :: Lens' TopicConfiguration (Maybe NotificationConfigurationFilter)
tcFilter = lens _tcFilter (\ s a -> s{_tcFilter = a})
tcTopicARN :: Lens' TopicConfiguration Text
tcTopicARN = lens _tcTopicARN (\ s a -> s{_tcTopicARN = a})
tcEvents :: Lens' TopicConfiguration [Event]
tcEvents = lens _tcEvents (\ s a -> s{_tcEvents = a}) . _Coerce
instance FromXML TopicConfiguration where
parseXML x
= TopicConfiguration' <$>
(x .@? "Id") <*> (x .@? "Filter") <*> (x .@ "Topic")
<*> (parseXMLList "Event" x)
instance Hashable TopicConfiguration where
instance NFData TopicConfiguration where
instance ToXML TopicConfiguration where
toXML TopicConfiguration'{..}
= mconcat
["Id" @= _tcId, "Filter" @= _tcFilter,
"Topic" @= _tcTopicARN, toXMLList "Event" _tcEvents]
data Transition = Transition'
{ _tDays :: !(Maybe Int)
, _tDate :: !(Maybe RFC822)
, _tStorageClass :: !(Maybe TransitionStorageClass)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
transition
:: Transition
transition =
Transition' {_tDays = Nothing, _tDate = Nothing, _tStorageClass = Nothing}
tDays :: Lens' Transition (Maybe Int)
tDays = lens _tDays (\ s a -> s{_tDays = a})
tDate :: Lens' Transition (Maybe UTCTime)
tDate = lens _tDate (\ s a -> s{_tDate = a}) . mapping _Time
tStorageClass :: Lens' Transition (Maybe TransitionStorageClass)
tStorageClass = lens _tStorageClass (\ s a -> s{_tStorageClass = a})
instance FromXML Transition where
parseXML x
= Transition' <$>
(x .@? "Days") <*> (x .@? "Date") <*>
(x .@? "StorageClass")
instance Hashable Transition where
instance NFData Transition where
instance ToXML Transition where
toXML Transition'{..}
= mconcat
["Days" @= _tDays, "Date" @= _tDate,
"StorageClass" @= _tStorageClass]
data VersioningConfiguration = VersioningConfiguration'
{ _vcStatus :: !(Maybe BucketVersioningStatus)
, _vcMFADelete :: !(Maybe MFADelete)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
versioningConfiguration
:: VersioningConfiguration
versioningConfiguration =
VersioningConfiguration' {_vcStatus = Nothing, _vcMFADelete = Nothing}
vcStatus :: Lens' VersioningConfiguration (Maybe BucketVersioningStatus)
vcStatus = lens _vcStatus (\ s a -> s{_vcStatus = a})
vcMFADelete :: Lens' VersioningConfiguration (Maybe MFADelete)
vcMFADelete = lens _vcMFADelete (\ s a -> s{_vcMFADelete = a})
instance Hashable VersioningConfiguration where
instance NFData VersioningConfiguration where
instance ToXML VersioningConfiguration where
toXML VersioningConfiguration'{..}
= mconcat
["Status" @= _vcStatus, "MfaDelete" @= _vcMFADelete]
data WebsiteConfiguration = WebsiteConfiguration'
{ _wcRedirectAllRequestsTo :: !(Maybe RedirectAllRequestsTo)
, _wcErrorDocument :: !(Maybe ErrorDocument)
, _wcIndexDocument :: !(Maybe IndexDocument)
, _wcRoutingRules :: !(Maybe [RoutingRule])
} deriving (Eq, Read, Show, Data, Typeable, Generic)
websiteConfiguration
:: WebsiteConfiguration
websiteConfiguration =
WebsiteConfiguration'
{ _wcRedirectAllRequestsTo = Nothing
, _wcErrorDocument = Nothing
, _wcIndexDocument = Nothing
, _wcRoutingRules = Nothing
}
wcRedirectAllRequestsTo :: Lens' WebsiteConfiguration (Maybe RedirectAllRequestsTo)
wcRedirectAllRequestsTo = lens _wcRedirectAllRequestsTo (\ s a -> s{_wcRedirectAllRequestsTo = a})
wcErrorDocument :: Lens' WebsiteConfiguration (Maybe ErrorDocument)
wcErrorDocument = lens _wcErrorDocument (\ s a -> s{_wcErrorDocument = a})
wcIndexDocument :: Lens' WebsiteConfiguration (Maybe IndexDocument)
wcIndexDocument = lens _wcIndexDocument (\ s a -> s{_wcIndexDocument = a})
wcRoutingRules :: Lens' WebsiteConfiguration [RoutingRule]
wcRoutingRules = lens _wcRoutingRules (\ s a -> s{_wcRoutingRules = a}) . _Default . _Coerce
instance Hashable WebsiteConfiguration where
instance NFData WebsiteConfiguration where
instance ToXML WebsiteConfiguration where
toXML WebsiteConfiguration'{..}
= mconcat
["RedirectAllRequestsTo" @= _wcRedirectAllRequestsTo,
"ErrorDocument" @= _wcErrorDocument,
"IndexDocument" @= _wcIndexDocument,
"RoutingRules" @=
toXML (toXMLList "RoutingRule" <$> _wcRoutingRules)]