{-# 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.LicenseManager.GetServiceSettings
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Gets the License Manager settings for the current Region.
module Amazonka.LicenseManager.GetServiceSettings
  ( -- * Creating a Request
    GetServiceSettings (..),
    newGetServiceSettings,

    -- * Destructuring the Response
    GetServiceSettingsResponse (..),
    newGetServiceSettingsResponse,

    -- * Response Lenses
    getServiceSettingsResponse_enableCrossAccountsDiscovery,
    getServiceSettingsResponse_licenseManagerResourceShareArn,
    getServiceSettingsResponse_organizationConfiguration,
    getServiceSettingsResponse_s3BucketArn,
    getServiceSettingsResponse_snsTopicArn,
    getServiceSettingsResponse_httpStatus,
  )
where

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

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

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

instance Core.AWSRequest GetServiceSettings where
  type
    AWSResponse GetServiceSettings =
      GetServiceSettingsResponse
  request :: (Service -> Service)
-> GetServiceSettings -> Request GetServiceSettings
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 GetServiceSettings
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse GetServiceSettings)))
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 Bool
-> Maybe Text
-> Maybe OrganizationConfiguration
-> Maybe Text
-> Maybe Text
-> Int
-> GetServiceSettingsResponse
GetServiceSettingsResponse'
            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
"EnableCrossAccountsDiscovery")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"LicenseManagerResourceShareArn")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"OrganizationConfiguration")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"S3BucketArn")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"SnsTopicArn")
            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 GetServiceSettings where
  hashWithSalt :: Int -> GetServiceSettings -> Int
hashWithSalt Int
_salt GetServiceSettings
_ =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` ()

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

instance Data.ToHeaders GetServiceSettings where
  toHeaders :: GetServiceSettings -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"X-Amz-Target"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"AWSLicenseManager.GetServiceSettings" ::
                          Prelude.ByteString
                      ),
            HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON GetServiceSettings where
  toJSON :: GetServiceSettings -> Value
toJSON = forall a b. a -> b -> a
Prelude.const (Object -> Value
Data.Object forall a. Monoid a => a
Prelude.mempty)

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

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

-- | /See:/ 'newGetServiceSettingsResponse' smart constructor.
data GetServiceSettingsResponse = GetServiceSettingsResponse'
  { -- | Indicates whether cross-account discovery is enabled.
    GetServiceSettingsResponse -> Maybe Bool
enableCrossAccountsDiscovery :: Prelude.Maybe Prelude.Bool,
    -- | Amazon Resource Name (ARN) of the resource share. The License Manager
    -- management account provides member accounts with access to this share.
    GetServiceSettingsResponse -> Maybe Text
licenseManagerResourceShareArn :: Prelude.Maybe Prelude.Text,
    -- | Indicates whether Organizations is integrated with License Manager for
    -- cross-account discovery.
    GetServiceSettingsResponse -> Maybe OrganizationConfiguration
organizationConfiguration :: Prelude.Maybe OrganizationConfiguration,
    -- | Regional S3 bucket path for storing reports, license trail event data,
    -- discovery data, and so on.
    GetServiceSettingsResponse -> Maybe Text
s3BucketArn :: Prelude.Maybe Prelude.Text,
    -- | SNS topic configured to receive notifications from License Manager.
    GetServiceSettingsResponse -> Maybe Text
snsTopicArn :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    GetServiceSettingsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetServiceSettingsResponse -> GetServiceSettingsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetServiceSettingsResponse -> GetServiceSettingsResponse -> Bool
$c/= :: GetServiceSettingsResponse -> GetServiceSettingsResponse -> Bool
== :: GetServiceSettingsResponse -> GetServiceSettingsResponse -> Bool
$c== :: GetServiceSettingsResponse -> GetServiceSettingsResponse -> Bool
Prelude.Eq, ReadPrec [GetServiceSettingsResponse]
ReadPrec GetServiceSettingsResponse
Int -> ReadS GetServiceSettingsResponse
ReadS [GetServiceSettingsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetServiceSettingsResponse]
$creadListPrec :: ReadPrec [GetServiceSettingsResponse]
readPrec :: ReadPrec GetServiceSettingsResponse
$creadPrec :: ReadPrec GetServiceSettingsResponse
readList :: ReadS [GetServiceSettingsResponse]
$creadList :: ReadS [GetServiceSettingsResponse]
readsPrec :: Int -> ReadS GetServiceSettingsResponse
$creadsPrec :: Int -> ReadS GetServiceSettingsResponse
Prelude.Read, Int -> GetServiceSettingsResponse -> ShowS
[GetServiceSettingsResponse] -> ShowS
GetServiceSettingsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetServiceSettingsResponse] -> ShowS
$cshowList :: [GetServiceSettingsResponse] -> ShowS
show :: GetServiceSettingsResponse -> String
$cshow :: GetServiceSettingsResponse -> String
showsPrec :: Int -> GetServiceSettingsResponse -> ShowS
$cshowsPrec :: Int -> GetServiceSettingsResponse -> ShowS
Prelude.Show, forall x.
Rep GetServiceSettingsResponse x -> GetServiceSettingsResponse
forall x.
GetServiceSettingsResponse -> Rep GetServiceSettingsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetServiceSettingsResponse x -> GetServiceSettingsResponse
$cfrom :: forall x.
GetServiceSettingsResponse -> Rep GetServiceSettingsResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetServiceSettingsResponse' 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:
--
-- 'enableCrossAccountsDiscovery', 'getServiceSettingsResponse_enableCrossAccountsDiscovery' - Indicates whether cross-account discovery is enabled.
--
-- 'licenseManagerResourceShareArn', 'getServiceSettingsResponse_licenseManagerResourceShareArn' - Amazon Resource Name (ARN) of the resource share. The License Manager
-- management account provides member accounts with access to this share.
--
-- 'organizationConfiguration', 'getServiceSettingsResponse_organizationConfiguration' - Indicates whether Organizations is integrated with License Manager for
-- cross-account discovery.
--
-- 's3BucketArn', 'getServiceSettingsResponse_s3BucketArn' - Regional S3 bucket path for storing reports, license trail event data,
-- discovery data, and so on.
--
-- 'snsTopicArn', 'getServiceSettingsResponse_snsTopicArn' - SNS topic configured to receive notifications from License Manager.
--
-- 'httpStatus', 'getServiceSettingsResponse_httpStatus' - The response's http status code.
newGetServiceSettingsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetServiceSettingsResponse
newGetServiceSettingsResponse :: Int -> GetServiceSettingsResponse
newGetServiceSettingsResponse Int
pHttpStatus_ =
  GetServiceSettingsResponse'
    { $sel:enableCrossAccountsDiscovery:GetServiceSettingsResponse' :: Maybe Bool
enableCrossAccountsDiscovery =
        forall a. Maybe a
Prelude.Nothing,
      $sel:licenseManagerResourceShareArn:GetServiceSettingsResponse' :: Maybe Text
licenseManagerResourceShareArn =
        forall a. Maybe a
Prelude.Nothing,
      $sel:organizationConfiguration:GetServiceSettingsResponse' :: Maybe OrganizationConfiguration
organizationConfiguration = forall a. Maybe a
Prelude.Nothing,
      $sel:s3BucketArn:GetServiceSettingsResponse' :: Maybe Text
s3BucketArn = forall a. Maybe a
Prelude.Nothing,
      $sel:snsTopicArn:GetServiceSettingsResponse' :: Maybe Text
snsTopicArn = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetServiceSettingsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Indicates whether cross-account discovery is enabled.
getServiceSettingsResponse_enableCrossAccountsDiscovery :: Lens.Lens' GetServiceSettingsResponse (Prelude.Maybe Prelude.Bool)
getServiceSettingsResponse_enableCrossAccountsDiscovery :: Lens' GetServiceSettingsResponse (Maybe Bool)
getServiceSettingsResponse_enableCrossAccountsDiscovery = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetServiceSettingsResponse' {Maybe Bool
enableCrossAccountsDiscovery :: Maybe Bool
$sel:enableCrossAccountsDiscovery:GetServiceSettingsResponse' :: GetServiceSettingsResponse -> Maybe Bool
enableCrossAccountsDiscovery} -> Maybe Bool
enableCrossAccountsDiscovery) (\s :: GetServiceSettingsResponse
s@GetServiceSettingsResponse' {} Maybe Bool
a -> GetServiceSettingsResponse
s {$sel:enableCrossAccountsDiscovery:GetServiceSettingsResponse' :: Maybe Bool
enableCrossAccountsDiscovery = Maybe Bool
a} :: GetServiceSettingsResponse)

-- | Amazon Resource Name (ARN) of the resource share. The License Manager
-- management account provides member accounts with access to this share.
getServiceSettingsResponse_licenseManagerResourceShareArn :: Lens.Lens' GetServiceSettingsResponse (Prelude.Maybe Prelude.Text)
getServiceSettingsResponse_licenseManagerResourceShareArn :: Lens' GetServiceSettingsResponse (Maybe Text)
getServiceSettingsResponse_licenseManagerResourceShareArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetServiceSettingsResponse' {Maybe Text
licenseManagerResourceShareArn :: Maybe Text
$sel:licenseManagerResourceShareArn:GetServiceSettingsResponse' :: GetServiceSettingsResponse -> Maybe Text
licenseManagerResourceShareArn} -> Maybe Text
licenseManagerResourceShareArn) (\s :: GetServiceSettingsResponse
s@GetServiceSettingsResponse' {} Maybe Text
a -> GetServiceSettingsResponse
s {$sel:licenseManagerResourceShareArn:GetServiceSettingsResponse' :: Maybe Text
licenseManagerResourceShareArn = Maybe Text
a} :: GetServiceSettingsResponse)

-- | Indicates whether Organizations is integrated with License Manager for
-- cross-account discovery.
getServiceSettingsResponse_organizationConfiguration :: Lens.Lens' GetServiceSettingsResponse (Prelude.Maybe OrganizationConfiguration)
getServiceSettingsResponse_organizationConfiguration :: Lens' GetServiceSettingsResponse (Maybe OrganizationConfiguration)
getServiceSettingsResponse_organizationConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetServiceSettingsResponse' {Maybe OrganizationConfiguration
organizationConfiguration :: Maybe OrganizationConfiguration
$sel:organizationConfiguration:GetServiceSettingsResponse' :: GetServiceSettingsResponse -> Maybe OrganizationConfiguration
organizationConfiguration} -> Maybe OrganizationConfiguration
organizationConfiguration) (\s :: GetServiceSettingsResponse
s@GetServiceSettingsResponse' {} Maybe OrganizationConfiguration
a -> GetServiceSettingsResponse
s {$sel:organizationConfiguration:GetServiceSettingsResponse' :: Maybe OrganizationConfiguration
organizationConfiguration = Maybe OrganizationConfiguration
a} :: GetServiceSettingsResponse)

-- | Regional S3 bucket path for storing reports, license trail event data,
-- discovery data, and so on.
getServiceSettingsResponse_s3BucketArn :: Lens.Lens' GetServiceSettingsResponse (Prelude.Maybe Prelude.Text)
getServiceSettingsResponse_s3BucketArn :: Lens' GetServiceSettingsResponse (Maybe Text)
getServiceSettingsResponse_s3BucketArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetServiceSettingsResponse' {Maybe Text
s3BucketArn :: Maybe Text
$sel:s3BucketArn:GetServiceSettingsResponse' :: GetServiceSettingsResponse -> Maybe Text
s3BucketArn} -> Maybe Text
s3BucketArn) (\s :: GetServiceSettingsResponse
s@GetServiceSettingsResponse' {} Maybe Text
a -> GetServiceSettingsResponse
s {$sel:s3BucketArn:GetServiceSettingsResponse' :: Maybe Text
s3BucketArn = Maybe Text
a} :: GetServiceSettingsResponse)

-- | SNS topic configured to receive notifications from License Manager.
getServiceSettingsResponse_snsTopicArn :: Lens.Lens' GetServiceSettingsResponse (Prelude.Maybe Prelude.Text)
getServiceSettingsResponse_snsTopicArn :: Lens' GetServiceSettingsResponse (Maybe Text)
getServiceSettingsResponse_snsTopicArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetServiceSettingsResponse' {Maybe Text
snsTopicArn :: Maybe Text
$sel:snsTopicArn:GetServiceSettingsResponse' :: GetServiceSettingsResponse -> Maybe Text
snsTopicArn} -> Maybe Text
snsTopicArn) (\s :: GetServiceSettingsResponse
s@GetServiceSettingsResponse' {} Maybe Text
a -> GetServiceSettingsResponse
s {$sel:snsTopicArn:GetServiceSettingsResponse' :: Maybe Text
snsTopicArn = Maybe Text
a} :: GetServiceSettingsResponse)

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

instance Prelude.NFData GetServiceSettingsResponse where
  rnf :: GetServiceSettingsResponse -> ()
rnf GetServiceSettingsResponse' {Int
Maybe Bool
Maybe Text
Maybe OrganizationConfiguration
httpStatus :: Int
snsTopicArn :: Maybe Text
s3BucketArn :: Maybe Text
organizationConfiguration :: Maybe OrganizationConfiguration
licenseManagerResourceShareArn :: Maybe Text
enableCrossAccountsDiscovery :: Maybe Bool
$sel:httpStatus:GetServiceSettingsResponse' :: GetServiceSettingsResponse -> Int
$sel:snsTopicArn:GetServiceSettingsResponse' :: GetServiceSettingsResponse -> Maybe Text
$sel:s3BucketArn:GetServiceSettingsResponse' :: GetServiceSettingsResponse -> Maybe Text
$sel:organizationConfiguration:GetServiceSettingsResponse' :: GetServiceSettingsResponse -> Maybe OrganizationConfiguration
$sel:licenseManagerResourceShareArn:GetServiceSettingsResponse' :: GetServiceSettingsResponse -> Maybe Text
$sel:enableCrossAccountsDiscovery:GetServiceSettingsResponse' :: GetServiceSettingsResponse -> Maybe Bool
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
enableCrossAccountsDiscovery
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
licenseManagerResourceShareArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe OrganizationConfiguration
organizationConfiguration
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
s3BucketArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
snsTopicArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus