{-# 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.ObjectLockConfiguration 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.ObjectLockEnabled
import Amazonka.S3.Types.ObjectLockRule
data ObjectLockConfiguration = ObjectLockConfiguration'
  { 
    
    
    ObjectLockConfiguration -> Maybe ObjectLockEnabled
objectLockEnabled :: Prelude.Maybe ObjectLockEnabled,
    
    
    
    
    
    ObjectLockConfiguration -> Maybe ObjectLockRule
rule :: Prelude.Maybe ObjectLockRule
  }
  deriving (ObjectLockConfiguration -> ObjectLockConfiguration -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ObjectLockConfiguration -> ObjectLockConfiguration -> Bool
$c/= :: ObjectLockConfiguration -> ObjectLockConfiguration -> Bool
== :: ObjectLockConfiguration -> ObjectLockConfiguration -> Bool
$c== :: ObjectLockConfiguration -> ObjectLockConfiguration -> Bool
Prelude.Eq, ReadPrec [ObjectLockConfiguration]
ReadPrec ObjectLockConfiguration
Int -> ReadS ObjectLockConfiguration
ReadS [ObjectLockConfiguration]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ObjectLockConfiguration]
$creadListPrec :: ReadPrec [ObjectLockConfiguration]
readPrec :: ReadPrec ObjectLockConfiguration
$creadPrec :: ReadPrec ObjectLockConfiguration
readList :: ReadS [ObjectLockConfiguration]
$creadList :: ReadS [ObjectLockConfiguration]
readsPrec :: Int -> ReadS ObjectLockConfiguration
$creadsPrec :: Int -> ReadS ObjectLockConfiguration
Prelude.Read, Int -> ObjectLockConfiguration -> ShowS
[ObjectLockConfiguration] -> ShowS
ObjectLockConfiguration -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ObjectLockConfiguration] -> ShowS
$cshowList :: [ObjectLockConfiguration] -> ShowS
show :: ObjectLockConfiguration -> String
$cshow :: ObjectLockConfiguration -> String
showsPrec :: Int -> ObjectLockConfiguration -> ShowS
$cshowsPrec :: Int -> ObjectLockConfiguration -> ShowS
Prelude.Show, forall x. Rep ObjectLockConfiguration x -> ObjectLockConfiguration
forall x. ObjectLockConfiguration -> Rep ObjectLockConfiguration x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ObjectLockConfiguration x -> ObjectLockConfiguration
$cfrom :: forall x. ObjectLockConfiguration -> Rep ObjectLockConfiguration x
Prelude.Generic)
newObjectLockConfiguration ::
  ObjectLockConfiguration
newObjectLockConfiguration :: ObjectLockConfiguration
newObjectLockConfiguration =
  ObjectLockConfiguration'
    { $sel:objectLockEnabled:ObjectLockConfiguration' :: Maybe ObjectLockEnabled
objectLockEnabled =
        forall a. Maybe a
Prelude.Nothing,
      $sel:rule:ObjectLockConfiguration' :: Maybe ObjectLockRule
rule = forall a. Maybe a
Prelude.Nothing
    }
objectLockConfiguration_objectLockEnabled :: Lens.Lens' ObjectLockConfiguration (Prelude.Maybe ObjectLockEnabled)
objectLockConfiguration_objectLockEnabled :: Lens' ObjectLockConfiguration (Maybe ObjectLockEnabled)
objectLockConfiguration_objectLockEnabled = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ObjectLockConfiguration' {Maybe ObjectLockEnabled
objectLockEnabled :: Maybe ObjectLockEnabled
$sel:objectLockEnabled:ObjectLockConfiguration' :: ObjectLockConfiguration -> Maybe ObjectLockEnabled
objectLockEnabled} -> Maybe ObjectLockEnabled
objectLockEnabled) (\s :: ObjectLockConfiguration
s@ObjectLockConfiguration' {} Maybe ObjectLockEnabled
a -> ObjectLockConfiguration
s {$sel:objectLockEnabled:ObjectLockConfiguration' :: Maybe ObjectLockEnabled
objectLockEnabled = Maybe ObjectLockEnabled
a} :: ObjectLockConfiguration)
objectLockConfiguration_rule :: Lens.Lens' ObjectLockConfiguration (Prelude.Maybe ObjectLockRule)
objectLockConfiguration_rule :: Lens' ObjectLockConfiguration (Maybe ObjectLockRule)
objectLockConfiguration_rule = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ObjectLockConfiguration' {Maybe ObjectLockRule
rule :: Maybe ObjectLockRule
$sel:rule:ObjectLockConfiguration' :: ObjectLockConfiguration -> Maybe ObjectLockRule
rule} -> Maybe ObjectLockRule
rule) (\s :: ObjectLockConfiguration
s@ObjectLockConfiguration' {} Maybe ObjectLockRule
a -> ObjectLockConfiguration
s {$sel:rule:ObjectLockConfiguration' :: Maybe ObjectLockRule
rule = Maybe ObjectLockRule
a} :: ObjectLockConfiguration)
instance Data.FromXML ObjectLockConfiguration where
  parseXML :: [Node] -> Either String ObjectLockConfiguration
parseXML [Node]
x =
    Maybe ObjectLockEnabled
-> Maybe ObjectLockRule -> ObjectLockConfiguration
ObjectLockConfiguration'
      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
"ObjectLockEnabled")
      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
"Rule")
instance Prelude.Hashable ObjectLockConfiguration where
  hashWithSalt :: Int -> ObjectLockConfiguration -> Int
hashWithSalt Int
_salt ObjectLockConfiguration' {Maybe ObjectLockEnabled
Maybe ObjectLockRule
rule :: Maybe ObjectLockRule
objectLockEnabled :: Maybe ObjectLockEnabled
$sel:rule:ObjectLockConfiguration' :: ObjectLockConfiguration -> Maybe ObjectLockRule
$sel:objectLockEnabled:ObjectLockConfiguration' :: ObjectLockConfiguration -> Maybe ObjectLockEnabled
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ObjectLockEnabled
objectLockEnabled
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ObjectLockRule
rule
instance Prelude.NFData ObjectLockConfiguration where
  rnf :: ObjectLockConfiguration -> ()
rnf ObjectLockConfiguration' {Maybe ObjectLockEnabled
Maybe ObjectLockRule
rule :: Maybe ObjectLockRule
objectLockEnabled :: Maybe ObjectLockEnabled
$sel:rule:ObjectLockConfiguration' :: ObjectLockConfiguration -> Maybe ObjectLockRule
$sel:objectLockEnabled:ObjectLockConfiguration' :: ObjectLockConfiguration -> Maybe ObjectLockEnabled
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe ObjectLockEnabled
objectLockEnabled
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ObjectLockRule
rule
instance Data.ToXML ObjectLockConfiguration where
  toXML :: ObjectLockConfiguration -> XML
toXML ObjectLockConfiguration' {Maybe ObjectLockEnabled
Maybe ObjectLockRule
rule :: Maybe ObjectLockRule
objectLockEnabled :: Maybe ObjectLockEnabled
$sel:rule:ObjectLockConfiguration' :: ObjectLockConfiguration -> Maybe ObjectLockRule
$sel:objectLockEnabled:ObjectLockConfiguration' :: ObjectLockConfiguration -> Maybe ObjectLockEnabled
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ Name
"ObjectLockEnabled" forall a. ToXML a => Name -> a -> XML
Data.@= Maybe ObjectLockEnabled
objectLockEnabled,
        Name
"Rule" forall a. ToXML a => Name -> a -> XML
Data.@= Maybe ObjectLockRule
rule
      ]