{-# 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.ErrorDocument
-- 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.ErrorDocument 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

-- | The error information.
--
-- /See:/ 'newErrorDocument' smart constructor.
data ErrorDocument = ErrorDocument'
  { -- | The object key name to use when a 4XX class error occurs.
    --
    -- 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>.
    ErrorDocument -> ObjectKey
key :: ObjectKey
  }
  deriving (ErrorDocument -> ErrorDocument -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ErrorDocument -> ErrorDocument -> Bool
$c/= :: ErrorDocument -> ErrorDocument -> Bool
== :: ErrorDocument -> ErrorDocument -> Bool
$c== :: ErrorDocument -> ErrorDocument -> Bool
Prelude.Eq, ReadPrec [ErrorDocument]
ReadPrec ErrorDocument
Int -> ReadS ErrorDocument
ReadS [ErrorDocument]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ErrorDocument]
$creadListPrec :: ReadPrec [ErrorDocument]
readPrec :: ReadPrec ErrorDocument
$creadPrec :: ReadPrec ErrorDocument
readList :: ReadS [ErrorDocument]
$creadList :: ReadS [ErrorDocument]
readsPrec :: Int -> ReadS ErrorDocument
$creadsPrec :: Int -> ReadS ErrorDocument
Prelude.Read, Int -> ErrorDocument -> ShowS
[ErrorDocument] -> ShowS
ErrorDocument -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ErrorDocument] -> ShowS
$cshowList :: [ErrorDocument] -> ShowS
show :: ErrorDocument -> String
$cshow :: ErrorDocument -> String
showsPrec :: Int -> ErrorDocument -> ShowS
$cshowsPrec :: Int -> ErrorDocument -> ShowS
Prelude.Show, forall x. Rep ErrorDocument x -> ErrorDocument
forall x. ErrorDocument -> Rep ErrorDocument x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ErrorDocument x -> ErrorDocument
$cfrom :: forall x. ErrorDocument -> Rep ErrorDocument x
Prelude.Generic)

-- |
-- Create a value of 'ErrorDocument' 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:
--
-- 'key', 'errorDocument_key' - The object key name to use when a 4XX class error occurs.
--
-- 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>.
newErrorDocument ::
  -- | 'key'
  ObjectKey ->
  ErrorDocument
newErrorDocument :: ObjectKey -> ErrorDocument
newErrorDocument ObjectKey
pKey_ = ErrorDocument' {$sel:key:ErrorDocument' :: ObjectKey
key = ObjectKey
pKey_}

-- | The object key name to use when a 4XX class error occurs.
--
-- 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>.
errorDocument_key :: Lens.Lens' ErrorDocument ObjectKey
errorDocument_key :: Lens' ErrorDocument ObjectKey
errorDocument_key = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ErrorDocument' {ObjectKey
key :: ObjectKey
$sel:key:ErrorDocument' :: ErrorDocument -> ObjectKey
key} -> ObjectKey
key) (\s :: ErrorDocument
s@ErrorDocument' {} ObjectKey
a -> ErrorDocument
s {$sel:key:ErrorDocument' :: ObjectKey
key = ObjectKey
a} :: ErrorDocument)

instance Data.FromXML ErrorDocument where
  parseXML :: [Node] -> Either String ErrorDocument
parseXML [Node]
x =
    ObjectKey -> ErrorDocument
ErrorDocument' forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String a
Data..@ Text
"Key")

instance Prelude.Hashable ErrorDocument where
  hashWithSalt :: Int -> ErrorDocument -> Int
hashWithSalt Int
_salt ErrorDocument' {ObjectKey
key :: ObjectKey
$sel:key:ErrorDocument' :: ErrorDocument -> ObjectKey
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` ObjectKey
key

instance Prelude.NFData ErrorDocument where
  rnf :: ErrorDocument -> ()
rnf ErrorDocument' {ObjectKey
key :: ObjectKey
$sel:key:ErrorDocument' :: ErrorDocument -> ObjectKey
..} = forall a. NFData a => a -> ()
Prelude.rnf ObjectKey
key

instance Data.ToXML ErrorDocument where
  toXML :: ErrorDocument -> XML
toXML ErrorDocument' {ObjectKey
key :: ObjectKey
$sel:key:ErrorDocument' :: ErrorDocument -> ObjectKey
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat [Name
"Key" forall a. ToXML a => Name -> a -> XML
Data.@= ObjectKey
key]