{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
{-# OPTIONS_GHC -fno-warn-unused-matches #-}
module Amazonka.S3.Types.InventoryConfiguration where
import qualified Amazonka.Core as Core
import qualified Amazonka.Lens as Lens
import qualified Amazonka.Prelude as Prelude
import Amazonka.S3.Internal
import Amazonka.S3.Types.InventoryDestination
import Amazonka.S3.Types.InventoryFilter
import Amazonka.S3.Types.InventoryIncludedObjectVersions
import Amazonka.S3.Types.InventoryOptionalField
import Amazonka.S3.Types.InventorySchedule
data InventoryConfiguration = InventoryConfiguration'
{
InventoryConfiguration -> Maybe [InventoryOptionalField]
optionalFields :: Prelude.Maybe [InventoryOptionalField],
InventoryConfiguration -> Maybe InventoryFilter
filter' :: Prelude.Maybe InventoryFilter,
InventoryConfiguration -> InventoryDestination
destination :: InventoryDestination,
InventoryConfiguration -> Bool
isEnabled :: Prelude.Bool,
InventoryConfiguration -> Text
id :: Prelude.Text,
InventoryConfiguration -> InventoryIncludedObjectVersions
includedObjectVersions :: InventoryIncludedObjectVersions,
InventoryConfiguration -> InventorySchedule
schedule :: InventorySchedule
}
deriving (InventoryConfiguration -> InventoryConfiguration -> Bool
(InventoryConfiguration -> InventoryConfiguration -> Bool)
-> (InventoryConfiguration -> InventoryConfiguration -> Bool)
-> Eq InventoryConfiguration
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: InventoryConfiguration -> InventoryConfiguration -> Bool
$c/= :: InventoryConfiguration -> InventoryConfiguration -> Bool
== :: InventoryConfiguration -> InventoryConfiguration -> Bool
$c== :: InventoryConfiguration -> InventoryConfiguration -> Bool
Prelude.Eq, Int -> InventoryConfiguration -> ShowS
[InventoryConfiguration] -> ShowS
InventoryConfiguration -> String
(Int -> InventoryConfiguration -> ShowS)
-> (InventoryConfiguration -> String)
-> ([InventoryConfiguration] -> ShowS)
-> Show InventoryConfiguration
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [InventoryConfiguration] -> ShowS
$cshowList :: [InventoryConfiguration] -> ShowS
show :: InventoryConfiguration -> String
$cshow :: InventoryConfiguration -> String
showsPrec :: Int -> InventoryConfiguration -> ShowS
$cshowsPrec :: Int -> InventoryConfiguration -> ShowS
Prelude.Show, (forall x. InventoryConfiguration -> Rep InventoryConfiguration x)
-> (forall x.
Rep InventoryConfiguration x -> InventoryConfiguration)
-> Generic InventoryConfiguration
forall x. Rep InventoryConfiguration x -> InventoryConfiguration
forall x. InventoryConfiguration -> Rep InventoryConfiguration x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep InventoryConfiguration x -> InventoryConfiguration
$cfrom :: forall x. InventoryConfiguration -> Rep InventoryConfiguration x
Prelude.Generic)
newInventoryConfiguration ::
InventoryDestination ->
Prelude.Bool ->
Prelude.Text ->
InventoryIncludedObjectVersions ->
InventorySchedule ->
InventoryConfiguration
newInventoryConfiguration :: InventoryDestination
-> Bool
-> Text
-> InventoryIncludedObjectVersions
-> InventorySchedule
-> InventoryConfiguration
newInventoryConfiguration
InventoryDestination
pDestination_
Bool
pIsEnabled_
Text
pId_
InventoryIncludedObjectVersions
pIncludedObjectVersions_
InventorySchedule
pSchedule_ =
InventoryConfiguration' :: Maybe [InventoryOptionalField]
-> Maybe InventoryFilter
-> InventoryDestination
-> Bool
-> Text
-> InventoryIncludedObjectVersions
-> InventorySchedule
-> InventoryConfiguration
InventoryConfiguration'
{ $sel:optionalFields:InventoryConfiguration' :: Maybe [InventoryOptionalField]
optionalFields =
Maybe [InventoryOptionalField]
forall a. Maybe a
Prelude.Nothing,
$sel:filter':InventoryConfiguration' :: Maybe InventoryFilter
filter' = Maybe InventoryFilter
forall a. Maybe a
Prelude.Nothing,
$sel:destination:InventoryConfiguration' :: InventoryDestination
destination = InventoryDestination
pDestination_,
$sel:isEnabled:InventoryConfiguration' :: Bool
isEnabled = Bool
pIsEnabled_,
$sel:id:InventoryConfiguration' :: Text
id = Text
pId_,
$sel:includedObjectVersions:InventoryConfiguration' :: InventoryIncludedObjectVersions
includedObjectVersions = InventoryIncludedObjectVersions
pIncludedObjectVersions_,
$sel:schedule:InventoryConfiguration' :: InventorySchedule
schedule = InventorySchedule
pSchedule_
}
inventoryConfiguration_optionalFields :: Lens.Lens' InventoryConfiguration (Prelude.Maybe [InventoryOptionalField])
inventoryConfiguration_optionalFields :: (Maybe [InventoryOptionalField]
-> f (Maybe [InventoryOptionalField]))
-> InventoryConfiguration -> f InventoryConfiguration
inventoryConfiguration_optionalFields = (InventoryConfiguration -> Maybe [InventoryOptionalField])
-> (InventoryConfiguration
-> Maybe [InventoryOptionalField] -> InventoryConfiguration)
-> Lens
InventoryConfiguration
InventoryConfiguration
(Maybe [InventoryOptionalField])
(Maybe [InventoryOptionalField])
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\InventoryConfiguration' {Maybe [InventoryOptionalField]
optionalFields :: Maybe [InventoryOptionalField]
$sel:optionalFields:InventoryConfiguration' :: InventoryConfiguration -> Maybe [InventoryOptionalField]
optionalFields} -> Maybe [InventoryOptionalField]
optionalFields) (\s :: InventoryConfiguration
s@InventoryConfiguration' {} Maybe [InventoryOptionalField]
a -> InventoryConfiguration
s {$sel:optionalFields:InventoryConfiguration' :: Maybe [InventoryOptionalField]
optionalFields = Maybe [InventoryOptionalField]
a} :: InventoryConfiguration) ((Maybe [InventoryOptionalField]
-> f (Maybe [InventoryOptionalField]))
-> InventoryConfiguration -> f InventoryConfiguration)
-> ((Maybe [InventoryOptionalField]
-> f (Maybe [InventoryOptionalField]))
-> Maybe [InventoryOptionalField]
-> f (Maybe [InventoryOptionalField]))
-> (Maybe [InventoryOptionalField]
-> f (Maybe [InventoryOptionalField]))
-> InventoryConfiguration
-> f InventoryConfiguration
forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. AnIso
[InventoryOptionalField]
[InventoryOptionalField]
[InventoryOptionalField]
[InventoryOptionalField]
-> Iso
(Maybe [InventoryOptionalField])
(Maybe [InventoryOptionalField])
(Maybe [InventoryOptionalField])
(Maybe [InventoryOptionalField])
forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping AnIso
[InventoryOptionalField]
[InventoryOptionalField]
[InventoryOptionalField]
[InventoryOptionalField]
forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced
inventoryConfiguration_filter :: Lens.Lens' InventoryConfiguration (Prelude.Maybe InventoryFilter)
inventoryConfiguration_filter :: (Maybe InventoryFilter -> f (Maybe InventoryFilter))
-> InventoryConfiguration -> f InventoryConfiguration
inventoryConfiguration_filter = (InventoryConfiguration -> Maybe InventoryFilter)
-> (InventoryConfiguration
-> Maybe InventoryFilter -> InventoryConfiguration)
-> Lens
InventoryConfiguration
InventoryConfiguration
(Maybe InventoryFilter)
(Maybe InventoryFilter)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\InventoryConfiguration' {Maybe InventoryFilter
filter' :: Maybe InventoryFilter
$sel:filter':InventoryConfiguration' :: InventoryConfiguration -> Maybe InventoryFilter
filter'} -> Maybe InventoryFilter
filter') (\s :: InventoryConfiguration
s@InventoryConfiguration' {} Maybe InventoryFilter
a -> InventoryConfiguration
s {$sel:filter':InventoryConfiguration' :: Maybe InventoryFilter
filter' = Maybe InventoryFilter
a} :: InventoryConfiguration)
inventoryConfiguration_destination :: Lens.Lens' InventoryConfiguration InventoryDestination
inventoryConfiguration_destination :: (InventoryDestination -> f InventoryDestination)
-> InventoryConfiguration -> f InventoryConfiguration
inventoryConfiguration_destination = (InventoryConfiguration -> InventoryDestination)
-> (InventoryConfiguration
-> InventoryDestination -> InventoryConfiguration)
-> Lens
InventoryConfiguration
InventoryConfiguration
InventoryDestination
InventoryDestination
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\InventoryConfiguration' {InventoryDestination
destination :: InventoryDestination
$sel:destination:InventoryConfiguration' :: InventoryConfiguration -> InventoryDestination
destination} -> InventoryDestination
destination) (\s :: InventoryConfiguration
s@InventoryConfiguration' {} InventoryDestination
a -> InventoryConfiguration
s {$sel:destination:InventoryConfiguration' :: InventoryDestination
destination = InventoryDestination
a} :: InventoryConfiguration)
inventoryConfiguration_isEnabled :: Lens.Lens' InventoryConfiguration Prelude.Bool
inventoryConfiguration_isEnabled :: (Bool -> f Bool)
-> InventoryConfiguration -> f InventoryConfiguration
inventoryConfiguration_isEnabled = (InventoryConfiguration -> Bool)
-> (InventoryConfiguration -> Bool -> InventoryConfiguration)
-> Lens InventoryConfiguration InventoryConfiguration Bool Bool
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\InventoryConfiguration' {Bool
isEnabled :: Bool
$sel:isEnabled:InventoryConfiguration' :: InventoryConfiguration -> Bool
isEnabled} -> Bool
isEnabled) (\s :: InventoryConfiguration
s@InventoryConfiguration' {} Bool
a -> InventoryConfiguration
s {$sel:isEnabled:InventoryConfiguration' :: Bool
isEnabled = Bool
a} :: InventoryConfiguration)
inventoryConfiguration_id :: Lens.Lens' InventoryConfiguration Prelude.Text
inventoryConfiguration_id :: (Text -> f Text)
-> InventoryConfiguration -> f InventoryConfiguration
inventoryConfiguration_id = (InventoryConfiguration -> Text)
-> (InventoryConfiguration -> Text -> InventoryConfiguration)
-> Lens InventoryConfiguration InventoryConfiguration Text Text
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\InventoryConfiguration' {Text
id :: Text
$sel:id:InventoryConfiguration' :: InventoryConfiguration -> Text
id} -> Text
id) (\s :: InventoryConfiguration
s@InventoryConfiguration' {} Text
a -> InventoryConfiguration
s {$sel:id:InventoryConfiguration' :: Text
id = Text
a} :: InventoryConfiguration)
inventoryConfiguration_includedObjectVersions :: Lens.Lens' InventoryConfiguration InventoryIncludedObjectVersions
inventoryConfiguration_includedObjectVersions :: (InventoryIncludedObjectVersions
-> f InventoryIncludedObjectVersions)
-> InventoryConfiguration -> f InventoryConfiguration
inventoryConfiguration_includedObjectVersions = (InventoryConfiguration -> InventoryIncludedObjectVersions)
-> (InventoryConfiguration
-> InventoryIncludedObjectVersions -> InventoryConfiguration)
-> Lens
InventoryConfiguration
InventoryConfiguration
InventoryIncludedObjectVersions
InventoryIncludedObjectVersions
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\InventoryConfiguration' {InventoryIncludedObjectVersions
includedObjectVersions :: InventoryIncludedObjectVersions
$sel:includedObjectVersions:InventoryConfiguration' :: InventoryConfiguration -> InventoryIncludedObjectVersions
includedObjectVersions} -> InventoryIncludedObjectVersions
includedObjectVersions) (\s :: InventoryConfiguration
s@InventoryConfiguration' {} InventoryIncludedObjectVersions
a -> InventoryConfiguration
s {$sel:includedObjectVersions:InventoryConfiguration' :: InventoryIncludedObjectVersions
includedObjectVersions = InventoryIncludedObjectVersions
a} :: InventoryConfiguration)
inventoryConfiguration_schedule :: Lens.Lens' InventoryConfiguration InventorySchedule
inventoryConfiguration_schedule :: (InventorySchedule -> f InventorySchedule)
-> InventoryConfiguration -> f InventoryConfiguration
inventoryConfiguration_schedule = (InventoryConfiguration -> InventorySchedule)
-> (InventoryConfiguration
-> InventorySchedule -> InventoryConfiguration)
-> Lens
InventoryConfiguration
InventoryConfiguration
InventorySchedule
InventorySchedule
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\InventoryConfiguration' {InventorySchedule
schedule :: InventorySchedule
$sel:schedule:InventoryConfiguration' :: InventoryConfiguration -> InventorySchedule
schedule} -> InventorySchedule
schedule) (\s :: InventoryConfiguration
s@InventoryConfiguration' {} InventorySchedule
a -> InventoryConfiguration
s {$sel:schedule:InventoryConfiguration' :: InventorySchedule
schedule = InventorySchedule
a} :: InventoryConfiguration)
instance Core.FromXML InventoryConfiguration where
parseXML :: [Node] -> Either String InventoryConfiguration
parseXML [Node]
x =
Maybe [InventoryOptionalField]
-> Maybe InventoryFilter
-> InventoryDestination
-> Bool
-> Text
-> InventoryIncludedObjectVersions
-> InventorySchedule
-> InventoryConfiguration
InventoryConfiguration'
(Maybe [InventoryOptionalField]
-> Maybe InventoryFilter
-> InventoryDestination
-> Bool
-> Text
-> InventoryIncludedObjectVersions
-> InventorySchedule
-> InventoryConfiguration)
-> Either String (Maybe [InventoryOptionalField])
-> Either
String
(Maybe InventoryFilter
-> InventoryDestination
-> Bool
-> Text
-> InventoryIncludedObjectVersions
-> InventorySchedule
-> InventoryConfiguration)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> ( [Node]
x [Node] -> Text -> Either String (Maybe [Node])
forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Core..@? Text
"OptionalFields" Either String (Maybe [Node]) -> [Node] -> Either String [Node]
forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ [Node]
forall a. Monoid a => a
Prelude.mempty
Either String [Node]
-> ([Node] -> Either String (Maybe [InventoryOptionalField]))
-> Either String (Maybe [InventoryOptionalField])
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
Prelude.>>= ([Node] -> Either String [InventoryOptionalField])
-> [Node] -> Either String (Maybe [InventoryOptionalField])
forall (f :: * -> *) a b.
Applicative f =>
([a] -> f b) -> [a] -> f (Maybe b)
Core.may (Text -> [Node] -> Either String [InventoryOptionalField]
forall a. FromXML a => Text -> [Node] -> Either String [a]
Core.parseXMLList Text
"Field")
)
Either
String
(Maybe InventoryFilter
-> InventoryDestination
-> Bool
-> Text
-> InventoryIncludedObjectVersions
-> InventorySchedule
-> InventoryConfiguration)
-> Either String (Maybe InventoryFilter)
-> Either
String
(InventoryDestination
-> Bool
-> Text
-> InventoryIncludedObjectVersions
-> InventorySchedule
-> InventoryConfiguration)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x [Node] -> Text -> Either String (Maybe InventoryFilter)
forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Core..@? Text
"Filter")
Either
String
(InventoryDestination
-> Bool
-> Text
-> InventoryIncludedObjectVersions
-> InventorySchedule
-> InventoryConfiguration)
-> Either String InventoryDestination
-> Either
String
(Bool
-> Text
-> InventoryIncludedObjectVersions
-> InventorySchedule
-> InventoryConfiguration)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x [Node] -> Text -> Either String InventoryDestination
forall a. FromXML a => [Node] -> Text -> Either String a
Core..@ Text
"Destination")
Either
String
(Bool
-> Text
-> InventoryIncludedObjectVersions
-> InventorySchedule
-> InventoryConfiguration)
-> Either String Bool
-> Either
String
(Text
-> InventoryIncludedObjectVersions
-> InventorySchedule
-> InventoryConfiguration)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x [Node] -> Text -> Either String Bool
forall a. FromXML a => [Node] -> Text -> Either String a
Core..@ Text
"IsEnabled")
Either
String
(Text
-> InventoryIncludedObjectVersions
-> InventorySchedule
-> InventoryConfiguration)
-> Either String Text
-> Either
String
(InventoryIncludedObjectVersions
-> InventorySchedule -> InventoryConfiguration)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x [Node] -> Text -> Either String Text
forall a. FromXML a => [Node] -> Text -> Either String a
Core..@ Text
"Id")
Either
String
(InventoryIncludedObjectVersions
-> InventorySchedule -> InventoryConfiguration)
-> Either String InventoryIncludedObjectVersions
-> Either String (InventorySchedule -> InventoryConfiguration)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x [Node] -> Text -> Either String InventoryIncludedObjectVersions
forall a. FromXML a => [Node] -> Text -> Either String a
Core..@ Text
"IncludedObjectVersions")
Either String (InventorySchedule -> InventoryConfiguration)
-> Either String InventorySchedule
-> Either String InventoryConfiguration
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x [Node] -> Text -> Either String InventorySchedule
forall a. FromXML a => [Node] -> Text -> Either String a
Core..@ Text
"Schedule")
instance Prelude.Hashable InventoryConfiguration
instance Prelude.NFData InventoryConfiguration
instance Core.ToXML InventoryConfiguration where
toXML :: InventoryConfiguration -> XML
toXML InventoryConfiguration' {Bool
Maybe [InventoryOptionalField]
Maybe InventoryFilter
Text
InventoryIncludedObjectVersions
InventorySchedule
InventoryDestination
schedule :: InventorySchedule
includedObjectVersions :: InventoryIncludedObjectVersions
id :: Text
isEnabled :: Bool
destination :: InventoryDestination
filter' :: Maybe InventoryFilter
optionalFields :: Maybe [InventoryOptionalField]
$sel:schedule:InventoryConfiguration' :: InventoryConfiguration -> InventorySchedule
$sel:includedObjectVersions:InventoryConfiguration' :: InventoryConfiguration -> InventoryIncludedObjectVersions
$sel:id:InventoryConfiguration' :: InventoryConfiguration -> Text
$sel:isEnabled:InventoryConfiguration' :: InventoryConfiguration -> Bool
$sel:destination:InventoryConfiguration' :: InventoryConfiguration -> InventoryDestination
$sel:filter':InventoryConfiguration' :: InventoryConfiguration -> Maybe InventoryFilter
$sel:optionalFields:InventoryConfiguration' :: InventoryConfiguration -> Maybe [InventoryOptionalField]
..} =
[XML] -> XML
forall a. Monoid a => [a] -> a
Prelude.mconcat
[ Name
"OptionalFields"
Name -> XML -> XML
forall a. ToXML a => Name -> a -> XML
Core.@= Maybe XML -> XML
forall a. ToXML a => a -> XML
Core.toXML
(Name -> [InventoryOptionalField] -> XML
forall a. (IsList a, ToXML (Item a)) => Name -> a -> XML
Core.toXMLList Name
"Field" ([InventoryOptionalField] -> XML)
-> Maybe [InventoryOptionalField] -> Maybe XML
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [InventoryOptionalField]
optionalFields),
Name
"Filter" Name -> Maybe InventoryFilter -> XML
forall a. ToXML a => Name -> a -> XML
Core.@= Maybe InventoryFilter
filter',
Name
"Destination" Name -> InventoryDestination -> XML
forall a. ToXML a => Name -> a -> XML
Core.@= InventoryDestination
destination,
Name
"IsEnabled" Name -> Bool -> XML
forall a. ToXML a => Name -> a -> XML
Core.@= Bool
isEnabled,
Name
"Id" Name -> Text -> XML
forall a. ToXML a => Name -> a -> XML
Core.@= Text
id,
Name
"IncludedObjectVersions"
Name -> InventoryIncludedObjectVersions -> XML
forall a. ToXML a => Name -> a -> XML
Core.@= InventoryIncludedObjectVersions
includedObjectVersions,
Name
"Schedule" Name -> InventorySchedule -> XML
forall a. ToXML a => Name -> a -> XML
Core.@= InventorySchedule
schedule
]