{-# 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.GetAlternateContact
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Retrieves 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.GetAlternateContact
  ( -- * Creating a Request
    GetAlternateContact (..),
    newGetAlternateContact,

    -- * Request Lenses
    getAlternateContact_accountId,
    getAlternateContact_alternateContactType,

    -- * Destructuring the Response
    GetAlternateContactResponse (..),
    newGetAlternateContactResponse,

    -- * Response Lenses
    getAlternateContactResponse_alternateContact,
    getAlternateContactResponse_httpStatus,
  )
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:/ 'newGetAlternateContact' smart constructor.
data GetAlternateContact = GetAlternateContact'
  { -- | 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.
    GetAlternateContact -> Maybe Text
accountId :: Prelude.Maybe Prelude.Text,
    -- | Specifies which alternate contact you want to retrieve.
    GetAlternateContact -> AlternateContactType
alternateContactType :: AlternateContactType
  }
  deriving (GetAlternateContact -> GetAlternateContact -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetAlternateContact -> GetAlternateContact -> Bool
$c/= :: GetAlternateContact -> GetAlternateContact -> Bool
== :: GetAlternateContact -> GetAlternateContact -> Bool
$c== :: GetAlternateContact -> GetAlternateContact -> Bool
Prelude.Eq, ReadPrec [GetAlternateContact]
ReadPrec GetAlternateContact
Int -> ReadS GetAlternateContact
ReadS [GetAlternateContact]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetAlternateContact]
$creadListPrec :: ReadPrec [GetAlternateContact]
readPrec :: ReadPrec GetAlternateContact
$creadPrec :: ReadPrec GetAlternateContact
readList :: ReadS [GetAlternateContact]
$creadList :: ReadS [GetAlternateContact]
readsPrec :: Int -> ReadS GetAlternateContact
$creadsPrec :: Int -> ReadS GetAlternateContact
Prelude.Read, Int -> GetAlternateContact -> ShowS
[GetAlternateContact] -> ShowS
GetAlternateContact -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetAlternateContact] -> ShowS
$cshowList :: [GetAlternateContact] -> ShowS
show :: GetAlternateContact -> String
$cshow :: GetAlternateContact -> String
showsPrec :: Int -> GetAlternateContact -> ShowS
$cshowsPrec :: Int -> GetAlternateContact -> ShowS
Prelude.Show, forall x. Rep GetAlternateContact x -> GetAlternateContact
forall x. GetAlternateContact -> Rep GetAlternateContact x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetAlternateContact x -> GetAlternateContact
$cfrom :: forall x. GetAlternateContact -> Rep GetAlternateContact x
Prelude.Generic)

-- |
-- Create a value of 'GetAlternateContact' 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', 'getAlternateContact_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', 'getAlternateContact_alternateContactType' - Specifies which alternate contact you want to retrieve.
newGetAlternateContact ::
  -- | 'alternateContactType'
  AlternateContactType ->
  GetAlternateContact
newGetAlternateContact :: AlternateContactType -> GetAlternateContact
newGetAlternateContact AlternateContactType
pAlternateContactType_ =
  GetAlternateContact'
    { $sel:accountId:GetAlternateContact' :: Maybe Text
accountId = forall a. Maybe a
Prelude.Nothing,
      $sel:alternateContactType:GetAlternateContact' :: AlternateContactType
alternateContactType = AlternateContactType
pAlternateContactType_
    }

-- | 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.
getAlternateContact_accountId :: Lens.Lens' GetAlternateContact (Prelude.Maybe Prelude.Text)
getAlternateContact_accountId :: Lens' GetAlternateContact (Maybe Text)
getAlternateContact_accountId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetAlternateContact' {Maybe Text
accountId :: Maybe Text
$sel:accountId:GetAlternateContact' :: GetAlternateContact -> Maybe Text
accountId} -> Maybe Text
accountId) (\s :: GetAlternateContact
s@GetAlternateContact' {} Maybe Text
a -> GetAlternateContact
s {$sel:accountId:GetAlternateContact' :: Maybe Text
accountId = Maybe Text
a} :: GetAlternateContact)

-- | Specifies which alternate contact you want to retrieve.
getAlternateContact_alternateContactType :: Lens.Lens' GetAlternateContact AlternateContactType
getAlternateContact_alternateContactType :: Lens' GetAlternateContact AlternateContactType
getAlternateContact_alternateContactType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetAlternateContact' {AlternateContactType
alternateContactType :: AlternateContactType
$sel:alternateContactType:GetAlternateContact' :: GetAlternateContact -> AlternateContactType
alternateContactType} -> AlternateContactType
alternateContactType) (\s :: GetAlternateContact
s@GetAlternateContact' {} AlternateContactType
a -> GetAlternateContact
s {$sel:alternateContactType:GetAlternateContact' :: AlternateContactType
alternateContactType = AlternateContactType
a} :: GetAlternateContact)

instance Core.AWSRequest GetAlternateContact where
  type
    AWSResponse GetAlternateContact =
      GetAlternateContactResponse
  request :: (Service -> Service)
-> GetAlternateContact -> Request GetAlternateContact
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 GetAlternateContact
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse GetAlternateContact)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> Object -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveJSON
      ( \Int
s ResponseHeaders
h Object
x ->
          Maybe AlternateContact -> Int -> GetAlternateContactResponse
GetAlternateContactResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"AlternateContact")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
      )

instance Prelude.Hashable GetAlternateContact where
  hashWithSalt :: Int -> GetAlternateContact -> Int
hashWithSalt Int
_salt GetAlternateContact' {Maybe Text
AlternateContactType
alternateContactType :: AlternateContactType
accountId :: Maybe Text
$sel:alternateContactType:GetAlternateContact' :: GetAlternateContact -> AlternateContactType
$sel:accountId:GetAlternateContact' :: GetAlternateContact -> 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

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

instance Data.ToHeaders GetAlternateContact where
  toHeaders :: GetAlternateContact -> ResponseHeaders
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 -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON GetAlternateContact where
  toJSON :: GetAlternateContact -> Value
toJSON GetAlternateContact' {Maybe Text
AlternateContactType
alternateContactType :: AlternateContactType
accountId :: Maybe Text
$sel:alternateContactType:GetAlternateContact' :: GetAlternateContact -> AlternateContactType
$sel:accountId:GetAlternateContact' :: GetAlternateContact -> 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
              )
          ]
      )

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

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

-- | /See:/ 'newGetAlternateContactResponse' smart constructor.
data GetAlternateContactResponse = GetAlternateContactResponse'
  { -- | A structure that contains the details for the specified alternate
    -- contact.
    GetAlternateContactResponse -> Maybe AlternateContact
alternateContact :: Prelude.Maybe AlternateContact,
    -- | The response's http status code.
    GetAlternateContactResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetAlternateContactResponse -> GetAlternateContactResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetAlternateContactResponse -> GetAlternateContactResponse -> Bool
$c/= :: GetAlternateContactResponse -> GetAlternateContactResponse -> Bool
== :: GetAlternateContactResponse -> GetAlternateContactResponse -> Bool
$c== :: GetAlternateContactResponse -> GetAlternateContactResponse -> Bool
Prelude.Eq, Int -> GetAlternateContactResponse -> ShowS
[GetAlternateContactResponse] -> ShowS
GetAlternateContactResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetAlternateContactResponse] -> ShowS
$cshowList :: [GetAlternateContactResponse] -> ShowS
show :: GetAlternateContactResponse -> String
$cshow :: GetAlternateContactResponse -> String
showsPrec :: Int -> GetAlternateContactResponse -> ShowS
$cshowsPrec :: Int -> GetAlternateContactResponse -> ShowS
Prelude.Show, forall x.
Rep GetAlternateContactResponse x -> GetAlternateContactResponse
forall x.
GetAlternateContactResponse -> Rep GetAlternateContactResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetAlternateContactResponse x -> GetAlternateContactResponse
$cfrom :: forall x.
GetAlternateContactResponse -> Rep GetAlternateContactResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetAlternateContactResponse' 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:
--
-- 'alternateContact', 'getAlternateContactResponse_alternateContact' - A structure that contains the details for the specified alternate
-- contact.
--
-- 'httpStatus', 'getAlternateContactResponse_httpStatus' - The response's http status code.
newGetAlternateContactResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetAlternateContactResponse
newGetAlternateContactResponse :: Int -> GetAlternateContactResponse
newGetAlternateContactResponse Int
pHttpStatus_ =
  GetAlternateContactResponse'
    { $sel:alternateContact:GetAlternateContactResponse' :: Maybe AlternateContact
alternateContact =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetAlternateContactResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | A structure that contains the details for the specified alternate
-- contact.
getAlternateContactResponse_alternateContact :: Lens.Lens' GetAlternateContactResponse (Prelude.Maybe AlternateContact)
getAlternateContactResponse_alternateContact :: Lens' GetAlternateContactResponse (Maybe AlternateContact)
getAlternateContactResponse_alternateContact = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetAlternateContactResponse' {Maybe AlternateContact
alternateContact :: Maybe AlternateContact
$sel:alternateContact:GetAlternateContactResponse' :: GetAlternateContactResponse -> Maybe AlternateContact
alternateContact} -> Maybe AlternateContact
alternateContact) (\s :: GetAlternateContactResponse
s@GetAlternateContactResponse' {} Maybe AlternateContact
a -> GetAlternateContactResponse
s {$sel:alternateContact:GetAlternateContactResponse' :: Maybe AlternateContact
alternateContact = Maybe AlternateContact
a} :: GetAlternateContactResponse)

-- | The response's http status code.
getAlternateContactResponse_httpStatus :: Lens.Lens' GetAlternateContactResponse Prelude.Int
getAlternateContactResponse_httpStatus :: Lens' GetAlternateContactResponse Int
getAlternateContactResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetAlternateContactResponse' {Int
httpStatus :: Int
$sel:httpStatus:GetAlternateContactResponse' :: GetAlternateContactResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: GetAlternateContactResponse
s@GetAlternateContactResponse' {} Int
a -> GetAlternateContactResponse
s {$sel:httpStatus:GetAlternateContactResponse' :: Int
httpStatus = Int
a} :: GetAlternateContactResponse)

instance Prelude.NFData GetAlternateContactResponse where
  rnf :: GetAlternateContactResponse -> ()
rnf GetAlternateContactResponse' {Int
Maybe AlternateContact
httpStatus :: Int
alternateContact :: Maybe AlternateContact
$sel:httpStatus:GetAlternateContactResponse' :: GetAlternateContactResponse -> Int
$sel:alternateContact:GetAlternateContactResponse' :: GetAlternateContactResponse -> Maybe AlternateContact
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe AlternateContact
alternateContact
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus