{-# 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 #-}

-- Derived from AWS service descriptions, licensed under Apache 2.0.

-- |
-- Module      : Amazonka.S3.Types.ReplicationRuleFilter
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
module Amazonka.S3.Types.ReplicationRuleFilter where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import qualified Amazonka.Prelude as Prelude
import Amazonka.S3.Internal
import Amazonka.S3.Types.ReplicationRuleAndOperator
import Amazonka.S3.Types.Tag

-- | A filter that identifies the subset of objects to which the replication
-- rule applies. A @Filter@ must specify exactly one @Prefix@, @Tag@, or an
-- @And@ child element.
--
-- /See:/ 'newReplicationRuleFilter' smart constructor.
data ReplicationRuleFilter = ReplicationRuleFilter'
  { -- | A container for specifying rule filters. The filters determine the
    -- subset of objects to which the rule applies. This element is required
    -- only if you specify more than one filter. For example:
    --
    -- -   If you specify both a @Prefix@ and a @Tag@ filter, wrap these
    --     filters in an @And@ tag.
    --
    -- -   If you specify a filter based on multiple tags, wrap the @Tag@
    --     elements in an @And@ tag.
    ReplicationRuleFilter -> Maybe ReplicationRuleAndOperator
and :: Prelude.Maybe ReplicationRuleAndOperator,
    -- | An object key name prefix that identifies the subset of objects to which
    -- the rule applies.
    --
    -- Replacement must be made for object keys containing special characters
    -- (such as carriage returns) when using XML requests. For more
    -- information, see
    -- <https://docs.aws.amazon.com/AmazonS3/latest/userguide/object-keys.html#object-key-xml-related-constraints XML related object key constraints>.
    ReplicationRuleFilter -> Maybe Text
prefix :: Prelude.Maybe Prelude.Text,
    -- | A container for specifying a tag key and value.
    --
    -- The rule applies only to objects that have the tag in their tag set.
    ReplicationRuleFilter -> Maybe Tag
tag :: Prelude.Maybe Tag
  }
  deriving (ReplicationRuleFilter -> ReplicationRuleFilter -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ReplicationRuleFilter -> ReplicationRuleFilter -> Bool
$c/= :: ReplicationRuleFilter -> ReplicationRuleFilter -> Bool
== :: ReplicationRuleFilter -> ReplicationRuleFilter -> Bool
$c== :: ReplicationRuleFilter -> ReplicationRuleFilter -> Bool
Prelude.Eq, ReadPrec [ReplicationRuleFilter]
ReadPrec ReplicationRuleFilter
Int -> ReadS ReplicationRuleFilter
ReadS [ReplicationRuleFilter]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ReplicationRuleFilter]
$creadListPrec :: ReadPrec [ReplicationRuleFilter]
readPrec :: ReadPrec ReplicationRuleFilter
$creadPrec :: ReadPrec ReplicationRuleFilter
readList :: ReadS [ReplicationRuleFilter]
$creadList :: ReadS [ReplicationRuleFilter]
readsPrec :: Int -> ReadS ReplicationRuleFilter
$creadsPrec :: Int -> ReadS ReplicationRuleFilter
Prelude.Read, Int -> ReplicationRuleFilter -> ShowS
[ReplicationRuleFilter] -> ShowS
ReplicationRuleFilter -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ReplicationRuleFilter] -> ShowS
$cshowList :: [ReplicationRuleFilter] -> ShowS
show :: ReplicationRuleFilter -> String
$cshow :: ReplicationRuleFilter -> String
showsPrec :: Int -> ReplicationRuleFilter -> ShowS
$cshowsPrec :: Int -> ReplicationRuleFilter -> ShowS
Prelude.Show, forall x. Rep ReplicationRuleFilter x -> ReplicationRuleFilter
forall x. ReplicationRuleFilter -> Rep ReplicationRuleFilter x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ReplicationRuleFilter x -> ReplicationRuleFilter
$cfrom :: forall x. ReplicationRuleFilter -> Rep ReplicationRuleFilter x
Prelude.Generic)

-- |
-- Create a value of 'ReplicationRuleFilter' with all optional fields omitted.
--
-- Use <https://hackage.haskell.org/package/generic-lens generic-lens> or <https://hackage.haskell.org/package/optics optics> to modify other optional fields.
--
-- The following record fields are available, with the corresponding lenses provided
-- for backwards compatibility:
--
-- 'and', 'replicationRuleFilter_and' - A container for specifying rule filters. The filters determine the
-- subset of objects to which the rule applies. This element is required
-- only if you specify more than one filter. For example:
--
-- -   If you specify both a @Prefix@ and a @Tag@ filter, wrap these
--     filters in an @And@ tag.
--
-- -   If you specify a filter based on multiple tags, wrap the @Tag@
--     elements in an @And@ tag.
--
-- 'prefix', 'replicationRuleFilter_prefix' - An object key name prefix that identifies the subset of objects to which
-- the rule applies.
--
-- Replacement must be made for object keys containing special characters
-- (such as carriage returns) when using XML requests. For more
-- information, see
-- <https://docs.aws.amazon.com/AmazonS3/latest/userguide/object-keys.html#object-key-xml-related-constraints XML related object key constraints>.
--
-- 'tag', 'replicationRuleFilter_tag' - A container for specifying a tag key and value.
--
-- The rule applies only to objects that have the tag in their tag set.
newReplicationRuleFilter ::
  ReplicationRuleFilter
newReplicationRuleFilter :: ReplicationRuleFilter
newReplicationRuleFilter =
  ReplicationRuleFilter'
    { $sel:and:ReplicationRuleFilter' :: Maybe ReplicationRuleAndOperator
and = forall a. Maybe a
Prelude.Nothing,
      $sel:prefix:ReplicationRuleFilter' :: Maybe Text
prefix = forall a. Maybe a
Prelude.Nothing,
      $sel:tag:ReplicationRuleFilter' :: Maybe Tag
tag = forall a. Maybe a
Prelude.Nothing
    }

-- | A container for specifying rule filters. The filters determine the
-- subset of objects to which the rule applies. This element is required
-- only if you specify more than one filter. For example:
--
-- -   If you specify both a @Prefix@ and a @Tag@ filter, wrap these
--     filters in an @And@ tag.
--
-- -   If you specify a filter based on multiple tags, wrap the @Tag@
--     elements in an @And@ tag.
replicationRuleFilter_and :: Lens.Lens' ReplicationRuleFilter (Prelude.Maybe ReplicationRuleAndOperator)
replicationRuleFilter_and :: Lens' ReplicationRuleFilter (Maybe ReplicationRuleAndOperator)
replicationRuleFilter_and = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ReplicationRuleFilter' {Maybe ReplicationRuleAndOperator
and :: Maybe ReplicationRuleAndOperator
$sel:and:ReplicationRuleFilter' :: ReplicationRuleFilter -> Maybe ReplicationRuleAndOperator
and} -> Maybe ReplicationRuleAndOperator
and) (\s :: ReplicationRuleFilter
s@ReplicationRuleFilter' {} Maybe ReplicationRuleAndOperator
a -> ReplicationRuleFilter
s {$sel:and:ReplicationRuleFilter' :: Maybe ReplicationRuleAndOperator
and = Maybe ReplicationRuleAndOperator
a} :: ReplicationRuleFilter)

-- | An object key name prefix that identifies the subset of objects to which
-- the rule applies.
--
-- Replacement must be made for object keys containing special characters
-- (such as carriage returns) when using XML requests. For more
-- information, see
-- <https://docs.aws.amazon.com/AmazonS3/latest/userguide/object-keys.html#object-key-xml-related-constraints XML related object key constraints>.
replicationRuleFilter_prefix :: Lens.Lens' ReplicationRuleFilter (Prelude.Maybe Prelude.Text)
replicationRuleFilter_prefix :: Lens' ReplicationRuleFilter (Maybe Text)
replicationRuleFilter_prefix = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ReplicationRuleFilter' {Maybe Text
prefix :: Maybe Text
$sel:prefix:ReplicationRuleFilter' :: ReplicationRuleFilter -> Maybe Text
prefix} -> Maybe Text
prefix) (\s :: ReplicationRuleFilter
s@ReplicationRuleFilter' {} Maybe Text
a -> ReplicationRuleFilter
s {$sel:prefix:ReplicationRuleFilter' :: Maybe Text
prefix = Maybe Text
a} :: ReplicationRuleFilter)

-- | A container for specifying a tag key and value.
--
-- The rule applies only to objects that have the tag in their tag set.
replicationRuleFilter_tag :: Lens.Lens' ReplicationRuleFilter (Prelude.Maybe Tag)
replicationRuleFilter_tag :: Lens' ReplicationRuleFilter (Maybe Tag)
replicationRuleFilter_tag = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ReplicationRuleFilter' {Maybe Tag
tag :: Maybe Tag
$sel:tag:ReplicationRuleFilter' :: ReplicationRuleFilter -> Maybe Tag
tag} -> Maybe Tag
tag) (\s :: ReplicationRuleFilter
s@ReplicationRuleFilter' {} Maybe Tag
a -> ReplicationRuleFilter
s {$sel:tag:ReplicationRuleFilter' :: Maybe Tag
tag = Maybe Tag
a} :: ReplicationRuleFilter)

instance Data.FromXML ReplicationRuleFilter where
  parseXML :: [Node] -> Either String ReplicationRuleFilter
parseXML [Node]
x =
    Maybe ReplicationRuleAndOperator
-> Maybe Text -> Maybe Tag -> ReplicationRuleFilter
ReplicationRuleFilter'
      forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"And")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"Prefix")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"Tag")

instance Prelude.Hashable ReplicationRuleFilter where
  hashWithSalt :: Int -> ReplicationRuleFilter -> Int
hashWithSalt Int
_salt ReplicationRuleFilter' {Maybe Text
Maybe Tag
Maybe ReplicationRuleAndOperator
tag :: Maybe Tag
prefix :: Maybe Text
and :: Maybe ReplicationRuleAndOperator
$sel:tag:ReplicationRuleFilter' :: ReplicationRuleFilter -> Maybe Tag
$sel:prefix:ReplicationRuleFilter' :: ReplicationRuleFilter -> Maybe Text
$sel:and:ReplicationRuleFilter' :: ReplicationRuleFilter -> Maybe ReplicationRuleAndOperator
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ReplicationRuleAndOperator
and
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
prefix
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Tag
tag

instance Prelude.NFData ReplicationRuleFilter where
  rnf :: ReplicationRuleFilter -> ()
rnf ReplicationRuleFilter' {Maybe Text
Maybe Tag
Maybe ReplicationRuleAndOperator
tag :: Maybe Tag
prefix :: Maybe Text
and :: Maybe ReplicationRuleAndOperator
$sel:tag:ReplicationRuleFilter' :: ReplicationRuleFilter -> Maybe Tag
$sel:prefix:ReplicationRuleFilter' :: ReplicationRuleFilter -> Maybe Text
$sel:and:ReplicationRuleFilter' :: ReplicationRuleFilter -> Maybe ReplicationRuleAndOperator
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe ReplicationRuleAndOperator
and
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
prefix
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Tag
tag

instance Data.ToXML ReplicationRuleFilter where
  toXML :: ReplicationRuleFilter -> XML
toXML ReplicationRuleFilter' {Maybe Text
Maybe Tag
Maybe ReplicationRuleAndOperator
tag :: Maybe Tag
prefix :: Maybe Text
and :: Maybe ReplicationRuleAndOperator
$sel:tag:ReplicationRuleFilter' :: ReplicationRuleFilter -> Maybe Tag
$sel:prefix:ReplicationRuleFilter' :: ReplicationRuleFilter -> Maybe Text
$sel:and:ReplicationRuleFilter' :: ReplicationRuleFilter -> Maybe ReplicationRuleAndOperator
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ Name
"And" forall a. ToXML a => Name -> a -> XML
Data.@= Maybe ReplicationRuleAndOperator
and,
        Name
"Prefix" forall a. ToXML a => Name -> a -> XML
Data.@= Maybe Text
prefix,
        Name
"Tag" forall a. ToXML a => Name -> a -> XML
Data.@= Maybe Tag
tag
      ]