{-# 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.MacieV2.GetMasterAccount
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- (Deprecated) Retrieves information about the Amazon Macie administrator
-- account for an account. This operation has been replaced by the
-- GetAdministratorAccount operation.
module Amazonka.MacieV2.GetMasterAccount
  ( -- * Creating a Request
    GetMasterAccount (..),
    newGetMasterAccount,

    -- * Destructuring the Response
    GetMasterAccountResponse (..),
    newGetMasterAccountResponse,

    -- * Response Lenses
    getMasterAccountResponse_master,
    getMasterAccountResponse_httpStatus,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.MacieV2.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

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

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

instance Core.AWSRequest GetMasterAccount where
  type
    AWSResponse GetMasterAccount =
      GetMasterAccountResponse
  request :: (Service -> Service)
-> GetMasterAccount -> Request GetMasterAccount
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.get (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy GetMasterAccount
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse GetMasterAccount)))
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 Invitation -> Int -> GetMasterAccountResponse
GetMasterAccountResponse'
            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
"master")
            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 GetMasterAccount where
  hashWithSalt :: Int -> GetMasterAccount -> Int
hashWithSalt Int
_salt GetMasterAccount
_ =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` ()

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

instance Data.ToHeaders GetMasterAccount where
  toHeaders :: GetMasterAccount -> 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.ToPath GetMasterAccount where
  toPath :: GetMasterAccount -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/master"

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

-- | /See:/ 'newGetMasterAccountResponse' smart constructor.
data GetMasterAccountResponse = GetMasterAccountResponse'
  { -- | (Deprecated) The Amazon Web Services account ID for the administrator
    -- account. If the accounts are associated by a Macie membership
    -- invitation, this object also provides details about the invitation that
    -- was sent to establish the relationship between the accounts.
    GetMasterAccountResponse -> Maybe Invitation
master :: Prelude.Maybe Invitation,
    -- | The response's http status code.
    GetMasterAccountResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetMasterAccountResponse -> GetMasterAccountResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetMasterAccountResponse -> GetMasterAccountResponse -> Bool
$c/= :: GetMasterAccountResponse -> GetMasterAccountResponse -> Bool
== :: GetMasterAccountResponse -> GetMasterAccountResponse -> Bool
$c== :: GetMasterAccountResponse -> GetMasterAccountResponse -> Bool
Prelude.Eq, ReadPrec [GetMasterAccountResponse]
ReadPrec GetMasterAccountResponse
Int -> ReadS GetMasterAccountResponse
ReadS [GetMasterAccountResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetMasterAccountResponse]
$creadListPrec :: ReadPrec [GetMasterAccountResponse]
readPrec :: ReadPrec GetMasterAccountResponse
$creadPrec :: ReadPrec GetMasterAccountResponse
readList :: ReadS [GetMasterAccountResponse]
$creadList :: ReadS [GetMasterAccountResponse]
readsPrec :: Int -> ReadS GetMasterAccountResponse
$creadsPrec :: Int -> ReadS GetMasterAccountResponse
Prelude.Read, Int -> GetMasterAccountResponse -> ShowS
[GetMasterAccountResponse] -> ShowS
GetMasterAccountResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetMasterAccountResponse] -> ShowS
$cshowList :: [GetMasterAccountResponse] -> ShowS
show :: GetMasterAccountResponse -> String
$cshow :: GetMasterAccountResponse -> String
showsPrec :: Int -> GetMasterAccountResponse -> ShowS
$cshowsPrec :: Int -> GetMasterAccountResponse -> ShowS
Prelude.Show, forall x.
Rep GetMasterAccountResponse x -> GetMasterAccountResponse
forall x.
GetMasterAccountResponse -> Rep GetMasterAccountResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetMasterAccountResponse x -> GetMasterAccountResponse
$cfrom :: forall x.
GetMasterAccountResponse -> Rep GetMasterAccountResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetMasterAccountResponse' 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:
--
-- 'master', 'getMasterAccountResponse_master' - (Deprecated) The Amazon Web Services account ID for the administrator
-- account. If the accounts are associated by a Macie membership
-- invitation, this object also provides details about the invitation that
-- was sent to establish the relationship between the accounts.
--
-- 'httpStatus', 'getMasterAccountResponse_httpStatus' - The response's http status code.
newGetMasterAccountResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetMasterAccountResponse
newGetMasterAccountResponse :: Int -> GetMasterAccountResponse
newGetMasterAccountResponse Int
pHttpStatus_ =
  GetMasterAccountResponse'
    { $sel:master:GetMasterAccountResponse' :: Maybe Invitation
master = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetMasterAccountResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | (Deprecated) The Amazon Web Services account ID for the administrator
-- account. If the accounts are associated by a Macie membership
-- invitation, this object also provides details about the invitation that
-- was sent to establish the relationship between the accounts.
getMasterAccountResponse_master :: Lens.Lens' GetMasterAccountResponse (Prelude.Maybe Invitation)
getMasterAccountResponse_master :: Lens' GetMasterAccountResponse (Maybe Invitation)
getMasterAccountResponse_master = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetMasterAccountResponse' {Maybe Invitation
master :: Maybe Invitation
$sel:master:GetMasterAccountResponse' :: GetMasterAccountResponse -> Maybe Invitation
master} -> Maybe Invitation
master) (\s :: GetMasterAccountResponse
s@GetMasterAccountResponse' {} Maybe Invitation
a -> GetMasterAccountResponse
s {$sel:master:GetMasterAccountResponse' :: Maybe Invitation
master = Maybe Invitation
a} :: GetMasterAccountResponse)

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

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