{-# 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.PutContactInformation
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Updates the primary contact information of an Amazon Web Services
-- account.
--
-- For complete details about how to use the primary contact operations,
-- see
-- <https://docs.aws.amazon.com/accounts/latest/reference/manage-acct-update-contact.html Update the primary and alternate contact information>.
module Amazonka.Account.PutContactInformation
  ( -- * Creating a Request
    PutContactInformation (..),
    newPutContactInformation,

    -- * Request Lenses
    putContactInformation_accountId,
    putContactInformation_contactInformation,

    -- * Destructuring the Response
    PutContactInformationResponse (..),
    newPutContactInformationResponse,
  )
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:/ 'newPutContactInformation' smart constructor.
data PutContactInformation = PutContactInformation'
  { -- | 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
    -- don\'t 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. The specified account ID must also
    -- 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, don\'t specify this parameter. Instead, call the operation
    -- using an identity belonging to the account whose contacts you wish to
    -- retrieve or modify.
    PutContactInformation -> Maybe Text
accountId :: Prelude.Maybe Prelude.Text,
    -- | Contains the details of the primary contact information associated with
    -- an Amazon Web Services account.
    PutContactInformation -> ContactInformation
contactInformation :: ContactInformation
  }
  deriving (PutContactInformation -> PutContactInformation -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PutContactInformation -> PutContactInformation -> Bool
$c/= :: PutContactInformation -> PutContactInformation -> Bool
== :: PutContactInformation -> PutContactInformation -> Bool
$c== :: PutContactInformation -> PutContactInformation -> Bool
Prelude.Eq, Int -> PutContactInformation -> ShowS
[PutContactInformation] -> ShowS
PutContactInformation -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PutContactInformation] -> ShowS
$cshowList :: [PutContactInformation] -> ShowS
show :: PutContactInformation -> String
$cshow :: PutContactInformation -> String
showsPrec :: Int -> PutContactInformation -> ShowS
$cshowsPrec :: Int -> PutContactInformation -> ShowS
Prelude.Show, forall x. Rep PutContactInformation x -> PutContactInformation
forall x. PutContactInformation -> Rep PutContactInformation x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PutContactInformation x -> PutContactInformation
$cfrom :: forall x. PutContactInformation -> Rep PutContactInformation x
Prelude.Generic)

-- |
-- Create a value of 'PutContactInformation' 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', 'putContactInformation_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
-- don\'t 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. The specified account ID must also
-- 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, don\'t specify this parameter. Instead, call the operation
-- using an identity belonging to the account whose contacts you wish to
-- retrieve or modify.
--
-- 'contactInformation', 'putContactInformation_contactInformation' - Contains the details of the primary contact information associated with
-- an Amazon Web Services account.
newPutContactInformation ::
  -- | 'contactInformation'
  ContactInformation ->
  PutContactInformation
newPutContactInformation :: ContactInformation -> PutContactInformation
newPutContactInformation ContactInformation
pContactInformation_ =
  PutContactInformation'
    { $sel:accountId:PutContactInformation' :: Maybe Text
accountId = forall a. Maybe a
Prelude.Nothing,
      $sel:contactInformation:PutContactInformation' :: ContactInformation
contactInformation = ContactInformation
pContactInformation_
    }

-- | 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
-- don\'t 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. The specified account ID must also
-- 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, don\'t specify this parameter. Instead, call the operation
-- using an identity belonging to the account whose contacts you wish to
-- retrieve or modify.
putContactInformation_accountId :: Lens.Lens' PutContactInformation (Prelude.Maybe Prelude.Text)
putContactInformation_accountId :: Lens' PutContactInformation (Maybe Text)
putContactInformation_accountId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PutContactInformation' {Maybe Text
accountId :: Maybe Text
$sel:accountId:PutContactInformation' :: PutContactInformation -> Maybe Text
accountId} -> Maybe Text
accountId) (\s :: PutContactInformation
s@PutContactInformation' {} Maybe Text
a -> PutContactInformation
s {$sel:accountId:PutContactInformation' :: Maybe Text
accountId = Maybe Text
a} :: PutContactInformation)

-- | Contains the details of the primary contact information associated with
-- an Amazon Web Services account.
putContactInformation_contactInformation :: Lens.Lens' PutContactInformation ContactInformation
putContactInformation_contactInformation :: Lens' PutContactInformation ContactInformation
putContactInformation_contactInformation = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PutContactInformation' {ContactInformation
contactInformation :: ContactInformation
$sel:contactInformation:PutContactInformation' :: PutContactInformation -> ContactInformation
contactInformation} -> ContactInformation
contactInformation) (\s :: PutContactInformation
s@PutContactInformation' {} ContactInformation
a -> PutContactInformation
s {$sel:contactInformation:PutContactInformation' :: ContactInformation
contactInformation = ContactInformation
a} :: PutContactInformation)

instance Core.AWSRequest PutContactInformation where
  type
    AWSResponse PutContactInformation =
      PutContactInformationResponse
  request :: (Service -> Service)
-> PutContactInformation -> Request PutContactInformation
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 PutContactInformation
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse PutContactInformation)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
AWSResponse a
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveNull PutContactInformationResponse
PutContactInformationResponse'

instance Prelude.Hashable PutContactInformation where
  hashWithSalt :: Int -> PutContactInformation -> Int
hashWithSalt Int
_salt PutContactInformation' {Maybe Text
ContactInformation
contactInformation :: ContactInformation
accountId :: Maybe Text
$sel:contactInformation:PutContactInformation' :: PutContactInformation -> ContactInformation
$sel:accountId:PutContactInformation' :: PutContactInformation -> 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` ContactInformation
contactInformation

instance Prelude.NFData PutContactInformation where
  rnf :: PutContactInformation -> ()
rnf PutContactInformation' {Maybe Text
ContactInformation
contactInformation :: ContactInformation
accountId :: Maybe Text
$sel:contactInformation:PutContactInformation' :: PutContactInformation -> ContactInformation
$sel:accountId:PutContactInformation' :: PutContactInformation -> 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 ContactInformation
contactInformation

instance Data.ToHeaders PutContactInformation where
  toHeaders :: PutContactInformation -> [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 PutContactInformation where
  toJSON :: PutContactInformation -> Value
toJSON PutContactInformation' {Maybe Text
ContactInformation
contactInformation :: ContactInformation
accountId :: Maybe Text
$sel:contactInformation:PutContactInformation' :: PutContactInformation -> ContactInformation
$sel:accountId:PutContactInformation' :: PutContactInformation -> 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
"ContactInformation" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= ContactInformation
contactInformation)
          ]
      )

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

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

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

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

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