{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# OPTIONS_GHC -fno-warn-unused-binds #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
{-# OPTIONS_GHC -fno-warn-unused-matches #-}

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

-- |
-- Module      : Amazonka.Account.PutAlternateContact
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Modifies the specified alternate contact attached to an Amazon Web
-- Services account.
--
-- For complete details about how to use the alternate contact operations,
-- see
-- <https://docs.aws.amazon.com/accounts/latest/reference/manage-acct-update-contact.html Access or updating the alternate contacts>.
--
-- Before you can update the alternate contact information for an Amazon
-- Web Services account that is managed by Organizations, you must first
-- enable integration between Amazon Web Services Account Management and
-- Organizations. For more information, see
-- <https://docs.aws.amazon.com/accounts/latest/reference/using-orgs-trusted-access.html Enabling trusted access for Amazon Web Services Account Management>.
module Amazonka.Account.PutAlternateContact
  ( -- * Creating a Request
    PutAlternateContact (..),
    newPutAlternateContact,

    -- * Request Lenses
    putAlternateContact_accountId,
    putAlternateContact_alternateContactType,
    putAlternateContact_emailAddress,
    putAlternateContact_name,
    putAlternateContact_phoneNumber,
    putAlternateContact_title,

    -- * Destructuring the Response
    PutAlternateContactResponse (..),
    newPutAlternateContactResponse,
  )
where

import Amazonka.Account.Types
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 qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newPutAlternateContact' smart constructor.
data PutAlternateContact = PutAlternateContact'
  { -- | Specifies the 12 digit account ID number of the Amazon Web Services
    -- account that you want to access or modify with this operation.
    --
    -- If you do not specify this parameter, it defaults to the Amazon Web
    -- Services account of the identity used to call the operation.
    --
    -- To use this parameter, the caller must be an identity in the
    -- <https://docs.aws.amazon.com/organizations/latest/userguide/orgs_getting-started_concepts.html#account organization\'s management account>
    -- or a delegated administrator account, and the specified account ID must
    -- be a member account in the same organization. The organization must have
    -- <https://docs.aws.amazon.com/organizations/latest/userguide/orgs_manage_org_support-all-features.html all features enabled>,
    -- and the organization must have
    -- <https://docs.aws.amazon.com/organizations/latest/userguide/using-orgs-trusted-access.html trusted access>
    -- enabled for the Account Management service, and optionally a
    -- <https://docs.aws.amazon.com/organizations/latest/userguide/using-orgs-delegated-admin.html delegated admin>
    -- account assigned.
    --
    -- The management account can\'t specify its own @AccountId@; it must call
    -- the operation in standalone context by not including the @AccountId@
    -- parameter.
    --
    -- To call this operation on an account that is not a member of an
    -- organization, then don\'t specify this parameter, and call the operation
    -- using an identity belonging to the account whose contacts you wish to
    -- retrieve or modify.
    PutAlternateContact -> Maybe Text
accountId :: Prelude.Maybe Prelude.Text,
    -- | Specifies which alternate contact you want to create or update.
    PutAlternateContact -> AlternateContactType
alternateContactType :: AlternateContactType,
    -- | Specifies an email address for the alternate contact.
    PutAlternateContact -> Sensitive Text
emailAddress :: Data.Sensitive Prelude.Text,
    -- | Specifies a name for the alternate contact.
    PutAlternateContact -> Sensitive Text
name :: Data.Sensitive Prelude.Text,
    -- | Specifies a phone number for the alternate contact.
    PutAlternateContact -> Sensitive Text
phoneNumber :: Data.Sensitive Prelude.Text,
    -- | Specifies a title for the alternate contact.
    PutAlternateContact -> Sensitive Text
title :: Data.Sensitive Prelude.Text
  }
  deriving (PutAlternateContact -> PutAlternateContact -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PutAlternateContact -> PutAlternateContact -> Bool
$c/= :: PutAlternateContact -> PutAlternateContact -> Bool
== :: PutAlternateContact -> PutAlternateContact -> Bool
$c== :: PutAlternateContact -> PutAlternateContact -> Bool
Prelude.Eq, Int -> PutAlternateContact -> ShowS
[PutAlternateContact] -> ShowS
PutAlternateContact -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PutAlternateContact] -> ShowS
$cshowList :: [PutAlternateContact] -> ShowS
show :: PutAlternateContact -> String
$cshow :: PutAlternateContact -> String
showsPrec :: Int -> PutAlternateContact -> ShowS
$cshowsPrec :: Int -> PutAlternateContact -> ShowS
Prelude.Show, forall x. Rep PutAlternateContact x -> PutAlternateContact
forall x. PutAlternateContact -> Rep PutAlternateContact x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PutAlternateContact x -> PutAlternateContact
$cfrom :: forall x. PutAlternateContact -> Rep PutAlternateContact x
Prelude.Generic)

-- |
-- Create a value of 'PutAlternateContact' 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:
--
-- 'accountId', 'putAlternateContact_accountId' - Specifies the 12 digit account ID number of the Amazon Web Services
-- account that you want to access or modify with this operation.
--
-- If you do not specify this parameter, it defaults to the Amazon Web
-- Services account of the identity used to call the operation.
--
-- To use this parameter, the caller must be an identity in the
-- <https://docs.aws.amazon.com/organizations/latest/userguide/orgs_getting-started_concepts.html#account organization\'s management account>
-- or a delegated administrator account, and the specified account ID must
-- be a member account in the same organization. The organization must have
-- <https://docs.aws.amazon.com/organizations/latest/userguide/orgs_manage_org_support-all-features.html all features enabled>,
-- and the organization must have
-- <https://docs.aws.amazon.com/organizations/latest/userguide/using-orgs-trusted-access.html trusted access>
-- enabled for the Account Management service, and optionally a
-- <https://docs.aws.amazon.com/organizations/latest/userguide/using-orgs-delegated-admin.html delegated admin>
-- account assigned.
--
-- The management account can\'t specify its own @AccountId@; it must call
-- the operation in standalone context by not including the @AccountId@
-- parameter.
--
-- To call this operation on an account that is not a member of an
-- organization, then don\'t specify this parameter, and call the operation
-- using an identity belonging to the account whose contacts you wish to
-- retrieve or modify.
--
-- 'alternateContactType', 'putAlternateContact_alternateContactType' - Specifies which alternate contact you want to create or update.
--
-- 'emailAddress', 'putAlternateContact_emailAddress' - Specifies an email address for the alternate contact.
--
-- 'name', 'putAlternateContact_name' - Specifies a name for the alternate contact.
--
-- 'phoneNumber', 'putAlternateContact_phoneNumber' - Specifies a phone number for the alternate contact.
--
-- 'title', 'putAlternateContact_title' - Specifies a title for the alternate contact.
newPutAlternateContact ::
  -- | 'alternateContactType'
  AlternateContactType ->
  -- | 'emailAddress'
  Prelude.Text ->
  -- | 'name'
  Prelude.Text ->
  -- | 'phoneNumber'
  Prelude.Text ->
  -- | 'title'
  Prelude.Text ->
  PutAlternateContact
newPutAlternateContact :: AlternateContactType
-> Text -> Text -> Text -> Text -> PutAlternateContact
newPutAlternateContact
  AlternateContactType
pAlternateContactType_
  Text
pEmailAddress_
  Text
pName_
  Text
pPhoneNumber_
  Text
pTitle_ =
    PutAlternateContact'
      { $sel:accountId:PutAlternateContact' :: Maybe Text
accountId = forall a. Maybe a
Prelude.Nothing,
        $sel:alternateContactType:PutAlternateContact' :: AlternateContactType
alternateContactType = AlternateContactType
pAlternateContactType_,
        $sel:emailAddress:PutAlternateContact' :: Sensitive Text
emailAddress = forall a. Iso' (Sensitive a) a
Data._Sensitive forall t b. AReview t b -> b -> t
Lens.# Text
pEmailAddress_,
        $sel:name:PutAlternateContact' :: Sensitive Text
name = forall a. Iso' (Sensitive a) a
Data._Sensitive forall t b. AReview t b -> b -> t
Lens.# Text
pName_,
        $sel:phoneNumber:PutAlternateContact' :: Sensitive Text
phoneNumber = forall a. Iso' (Sensitive a) a
Data._Sensitive forall t b. AReview t b -> b -> t
Lens.# Text
pPhoneNumber_,
        $sel:title:PutAlternateContact' :: Sensitive Text
title = forall a. Iso' (Sensitive a) a
Data._Sensitive forall t b. AReview t b -> b -> t
Lens.# Text
pTitle_
      }

-- | Specifies the 12 digit account ID number of the Amazon Web Services
-- account that you want to access or modify with this operation.
--
-- If you do not specify this parameter, it defaults to the Amazon Web
-- Services account of the identity used to call the operation.
--
-- To use this parameter, the caller must be an identity in the
-- <https://docs.aws.amazon.com/organizations/latest/userguide/orgs_getting-started_concepts.html#account organization\'s management account>
-- or a delegated administrator account, and the specified account ID must
-- be a member account in the same organization. The organization must have
-- <https://docs.aws.amazon.com/organizations/latest/userguide/orgs_manage_org_support-all-features.html all features enabled>,
-- and the organization must have
-- <https://docs.aws.amazon.com/organizations/latest/userguide/using-orgs-trusted-access.html trusted access>
-- enabled for the Account Management service, and optionally a
-- <https://docs.aws.amazon.com/organizations/latest/userguide/using-orgs-delegated-admin.html delegated admin>
-- account assigned.
--
-- The management account can\'t specify its own @AccountId@; it must call
-- the operation in standalone context by not including the @AccountId@
-- parameter.
--
-- To call this operation on an account that is not a member of an
-- organization, then don\'t specify this parameter, and call the operation
-- using an identity belonging to the account whose contacts you wish to
-- retrieve or modify.
putAlternateContact_accountId :: Lens.Lens' PutAlternateContact (Prelude.Maybe Prelude.Text)
putAlternateContact_accountId :: Lens' PutAlternateContact (Maybe Text)
putAlternateContact_accountId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PutAlternateContact' {Maybe Text
accountId :: Maybe Text
$sel:accountId:PutAlternateContact' :: PutAlternateContact -> Maybe Text
accountId} -> Maybe Text
accountId) (\s :: PutAlternateContact
s@PutAlternateContact' {} Maybe Text
a -> PutAlternateContact
s {$sel:accountId:PutAlternateContact' :: Maybe Text
accountId = Maybe Text
a} :: PutAlternateContact)

-- | Specifies which alternate contact you want to create or update.
putAlternateContact_alternateContactType :: Lens.Lens' PutAlternateContact AlternateContactType
putAlternateContact_alternateContactType :: Lens' PutAlternateContact AlternateContactType
putAlternateContact_alternateContactType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PutAlternateContact' {AlternateContactType
alternateContactType :: AlternateContactType
$sel:alternateContactType:PutAlternateContact' :: PutAlternateContact -> AlternateContactType
alternateContactType} -> AlternateContactType
alternateContactType) (\s :: PutAlternateContact
s@PutAlternateContact' {} AlternateContactType
a -> PutAlternateContact
s {$sel:alternateContactType:PutAlternateContact' :: AlternateContactType
alternateContactType = AlternateContactType
a} :: PutAlternateContact)

-- | Specifies an email address for the alternate contact.
putAlternateContact_emailAddress :: Lens.Lens' PutAlternateContact Prelude.Text
putAlternateContact_emailAddress :: Lens' PutAlternateContact Text
putAlternateContact_emailAddress = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PutAlternateContact' {Sensitive Text
emailAddress :: Sensitive Text
$sel:emailAddress:PutAlternateContact' :: PutAlternateContact -> Sensitive Text
emailAddress} -> Sensitive Text
emailAddress) (\s :: PutAlternateContact
s@PutAlternateContact' {} Sensitive Text
a -> PutAlternateContact
s {$sel:emailAddress:PutAlternateContact' :: Sensitive Text
emailAddress = Sensitive Text
a} :: PutAlternateContact) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a. Iso' (Sensitive a) a
Data._Sensitive

-- | Specifies a name for the alternate contact.
putAlternateContact_name :: Lens.Lens' PutAlternateContact Prelude.Text
putAlternateContact_name :: Lens' PutAlternateContact Text
putAlternateContact_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PutAlternateContact' {Sensitive Text
name :: Sensitive Text
$sel:name:PutAlternateContact' :: PutAlternateContact -> Sensitive Text
name} -> Sensitive Text
name) (\s :: PutAlternateContact
s@PutAlternateContact' {} Sensitive Text
a -> PutAlternateContact
s {$sel:name:PutAlternateContact' :: Sensitive Text
name = Sensitive Text
a} :: PutAlternateContact) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a. Iso' (Sensitive a) a
Data._Sensitive

-- | Specifies a phone number for the alternate contact.
putAlternateContact_phoneNumber :: Lens.Lens' PutAlternateContact Prelude.Text
putAlternateContact_phoneNumber :: Lens' PutAlternateContact Text
putAlternateContact_phoneNumber = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PutAlternateContact' {Sensitive Text
phoneNumber :: Sensitive Text
$sel:phoneNumber:PutAlternateContact' :: PutAlternateContact -> Sensitive Text
phoneNumber} -> Sensitive Text
phoneNumber) (\s :: PutAlternateContact
s@PutAlternateContact' {} Sensitive Text
a -> PutAlternateContact
s {$sel:phoneNumber:PutAlternateContact' :: Sensitive Text
phoneNumber = Sensitive Text
a} :: PutAlternateContact) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a. Iso' (Sensitive a) a
Data._Sensitive

-- | Specifies a title for the alternate contact.
putAlternateContact_title :: Lens.Lens' PutAlternateContact Prelude.Text
putAlternateContact_title :: Lens' PutAlternateContact Text
putAlternateContact_title = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PutAlternateContact' {Sensitive Text
title :: Sensitive Text
$sel:title:PutAlternateContact' :: PutAlternateContact -> Sensitive Text
title} -> Sensitive Text
title) (\s :: PutAlternateContact
s@PutAlternateContact' {} Sensitive Text
a -> PutAlternateContact
s {$sel:title:PutAlternateContact' :: Sensitive Text
title = Sensitive Text
a} :: PutAlternateContact) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a. Iso' (Sensitive a) a
Data._Sensitive

instance Core.AWSRequest PutAlternateContact where
  type
    AWSResponse PutAlternateContact =
      PutAlternateContactResponse
  request :: (Service -> Service)
-> PutAlternateContact -> Request PutAlternateContact
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.postJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy PutAlternateContact
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse PutAlternateContact)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
AWSResponse a
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveNull PutAlternateContactResponse
PutAlternateContactResponse'

instance Prelude.Hashable PutAlternateContact where
  hashWithSalt :: Int -> PutAlternateContact -> Int
hashWithSalt Int
_salt PutAlternateContact' {Maybe Text
Sensitive Text
AlternateContactType
title :: Sensitive Text
phoneNumber :: Sensitive Text
name :: Sensitive Text
emailAddress :: Sensitive Text
alternateContactType :: AlternateContactType
accountId :: Maybe Text
$sel:title:PutAlternateContact' :: PutAlternateContact -> Sensitive Text
$sel:phoneNumber:PutAlternateContact' :: PutAlternateContact -> Sensitive Text
$sel:name:PutAlternateContact' :: PutAlternateContact -> Sensitive Text
$sel:emailAddress:PutAlternateContact' :: PutAlternateContact -> Sensitive Text
$sel:alternateContactType:PutAlternateContact' :: PutAlternateContact -> AlternateContactType
$sel:accountId:PutAlternateContact' :: PutAlternateContact -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
accountId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` AlternateContactType
alternateContactType
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Sensitive Text
emailAddress
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Sensitive Text
name
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Sensitive Text
phoneNumber
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Sensitive Text
title

instance Prelude.NFData PutAlternateContact where
  rnf :: PutAlternateContact -> ()
rnf PutAlternateContact' {Maybe Text
Sensitive Text
AlternateContactType
title :: Sensitive Text
phoneNumber :: Sensitive Text
name :: Sensitive Text
emailAddress :: Sensitive Text
alternateContactType :: AlternateContactType
accountId :: Maybe Text
$sel:title:PutAlternateContact' :: PutAlternateContact -> Sensitive Text
$sel:phoneNumber:PutAlternateContact' :: PutAlternateContact -> Sensitive Text
$sel:name:PutAlternateContact' :: PutAlternateContact -> Sensitive Text
$sel:emailAddress:PutAlternateContact' :: PutAlternateContact -> Sensitive Text
$sel:alternateContactType:PutAlternateContact' :: PutAlternateContact -> AlternateContactType
$sel:accountId:PutAlternateContact' :: PutAlternateContact -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
accountId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf AlternateContactType
alternateContactType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Sensitive Text
emailAddress
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Sensitive Text
name
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Sensitive Text
phoneNumber
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Sensitive Text
title

instance Data.ToHeaders PutAlternateContact where
  toHeaders :: PutAlternateContact -> [Header]
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> [Header]
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON PutAlternateContact where
  toJSON :: PutAlternateContact -> Value
toJSON PutAlternateContact' {Maybe Text
Sensitive Text
AlternateContactType
title :: Sensitive Text
phoneNumber :: Sensitive Text
name :: Sensitive Text
emailAddress :: Sensitive Text
alternateContactType :: AlternateContactType
accountId :: Maybe Text
$sel:title:PutAlternateContact' :: PutAlternateContact -> Sensitive Text
$sel:phoneNumber:PutAlternateContact' :: PutAlternateContact -> Sensitive Text
$sel:name:PutAlternateContact' :: PutAlternateContact -> Sensitive Text
$sel:emailAddress:PutAlternateContact' :: PutAlternateContact -> Sensitive Text
$sel:alternateContactType:PutAlternateContact' :: PutAlternateContact -> AlternateContactType
$sel:accountId:PutAlternateContact' :: PutAlternateContact -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"AccountId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
accountId,
            forall a. a -> Maybe a
Prelude.Just
              ( Key
"AlternateContactType"
                  forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= AlternateContactType
alternateContactType
              ),
            forall a. a -> Maybe a
Prelude.Just (Key
"EmailAddress" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Sensitive Text
emailAddress),
            forall a. a -> Maybe a
Prelude.Just (Key
"Name" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Sensitive Text
name),
            forall a. a -> Maybe a
Prelude.Just (Key
"PhoneNumber" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Sensitive Text
phoneNumber),
            forall a. a -> Maybe a
Prelude.Just (Key
"Title" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Sensitive Text
title)
          ]
      )

instance Data.ToPath PutAlternateContact where
  toPath :: PutAlternateContact -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/putAlternateContact"

instance Data.ToQuery PutAlternateContact where
  toQuery :: PutAlternateContact -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

-- | /See:/ 'newPutAlternateContactResponse' smart constructor.
data PutAlternateContactResponse = PutAlternateContactResponse'
  {
  }
  deriving (PutAlternateContactResponse -> PutAlternateContactResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PutAlternateContactResponse -> PutAlternateContactResponse -> Bool
$c/= :: PutAlternateContactResponse -> PutAlternateContactResponse -> Bool
== :: PutAlternateContactResponse -> PutAlternateContactResponse -> Bool
$c== :: PutAlternateContactResponse -> PutAlternateContactResponse -> Bool
Prelude.Eq, ReadPrec [PutAlternateContactResponse]
ReadPrec PutAlternateContactResponse
Int -> ReadS PutAlternateContactResponse
ReadS [PutAlternateContactResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [PutAlternateContactResponse]
$creadListPrec :: ReadPrec [PutAlternateContactResponse]
readPrec :: ReadPrec PutAlternateContactResponse
$creadPrec :: ReadPrec PutAlternateContactResponse
readList :: ReadS [PutAlternateContactResponse]
$creadList :: ReadS [PutAlternateContactResponse]
readsPrec :: Int -> ReadS PutAlternateContactResponse
$creadsPrec :: Int -> ReadS PutAlternateContactResponse
Prelude.Read, Int -> PutAlternateContactResponse -> ShowS
[PutAlternateContactResponse] -> ShowS
PutAlternateContactResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PutAlternateContactResponse] -> ShowS
$cshowList :: [PutAlternateContactResponse] -> ShowS
show :: PutAlternateContactResponse -> String
$cshow :: PutAlternateContactResponse -> String
showsPrec :: Int -> PutAlternateContactResponse -> ShowS
$cshowsPrec :: Int -> PutAlternateContactResponse -> ShowS
Prelude.Show, forall x.
Rep PutAlternateContactResponse x -> PutAlternateContactResponse
forall x.
PutAlternateContactResponse -> Rep PutAlternateContactResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep PutAlternateContactResponse x -> PutAlternateContactResponse
$cfrom :: forall x.
PutAlternateContactResponse -> Rep PutAlternateContactResponse x
Prelude.Generic)

-- |
-- Create a value of 'PutAlternateContactResponse' 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.
newPutAlternateContactResponse ::
  PutAlternateContactResponse
newPutAlternateContactResponse :: PutAlternateContactResponse
newPutAlternateContactResponse =
  PutAlternateContactResponse
PutAlternateContactResponse'

instance Prelude.NFData PutAlternateContactResponse where
  rnf :: PutAlternateContactResponse -> ()
rnf PutAlternateContactResponse
_ = ()