{-# 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.LicenseManagerLinuxSubscriptions.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)
--
-- Lists the Linux subscriptions service settings.
module Amazonka.LicenseManagerLinuxSubscriptions.GetServiceSettings
  ( -- * Creating a Request
    GetServiceSettings (..),
    newGetServiceSettings,

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

    -- * Response Lenses
    getServiceSettingsResponse_homeRegions,
    getServiceSettingsResponse_linuxSubscriptionsDiscovery,
    getServiceSettingsResponse_linuxSubscriptionsDiscoverySettings,
    getServiceSettingsResponse_status,
    getServiceSettingsResponse_statusMessage,
    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.LicenseManagerLinuxSubscriptions.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 (NonEmpty Text)
-> Maybe LinuxSubscriptionsDiscovery
-> Maybe LinuxSubscriptionsDiscoverySettings
-> Maybe Status
-> Maybe (HashMap Text 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
"HomeRegions")
            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
"LinuxSubscriptionsDiscovery")
            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
"LinuxSubscriptionsDiscoverySettings")
            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
"Status")
            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
"StatusMessage" forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty)
            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
"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
"/subscription/GetServiceSettings"

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'
  { -- | The Region in which License Manager displays the aggregated data for
    -- Linux subscriptions.
    GetServiceSettingsResponse -> Maybe (NonEmpty Text)
homeRegions :: Prelude.Maybe (Prelude.NonEmpty Prelude.Text),
    -- | Lists if discovery has been enabled for Linux subscriptions.
    GetServiceSettingsResponse -> Maybe LinuxSubscriptionsDiscovery
linuxSubscriptionsDiscovery :: Prelude.Maybe LinuxSubscriptionsDiscovery,
    -- | Lists the settings defined for Linux subscriptions discovery. The
    -- settings include if Organizations integration has been enabled, and
    -- which Regions data will be aggregated from.
    GetServiceSettingsResponse
-> Maybe LinuxSubscriptionsDiscoverySettings
linuxSubscriptionsDiscoverySettings :: Prelude.Maybe LinuxSubscriptionsDiscoverySettings,
    -- | Indicates the status of Linux subscriptions settings being applied.
    GetServiceSettingsResponse -> Maybe Status
status :: Prelude.Maybe Status,
    -- | A message which details the Linux subscriptions service settings current
    -- status.
    GetServiceSettingsResponse -> Maybe (HashMap Text Text)
statusMessage :: Prelude.Maybe (Prelude.HashMap Prelude.Text 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:
--
-- 'homeRegions', 'getServiceSettingsResponse_homeRegions' - The Region in which License Manager displays the aggregated data for
-- Linux subscriptions.
--
-- 'linuxSubscriptionsDiscovery', 'getServiceSettingsResponse_linuxSubscriptionsDiscovery' - Lists if discovery has been enabled for Linux subscriptions.
--
-- 'linuxSubscriptionsDiscoverySettings', 'getServiceSettingsResponse_linuxSubscriptionsDiscoverySettings' - Lists the settings defined for Linux subscriptions discovery. The
-- settings include if Organizations integration has been enabled, and
-- which Regions data will be aggregated from.
--
-- 'status', 'getServiceSettingsResponse_status' - Indicates the status of Linux subscriptions settings being applied.
--
-- 'statusMessage', 'getServiceSettingsResponse_statusMessage' - A message which details the Linux subscriptions service settings current
-- status.
--
-- 'httpStatus', 'getServiceSettingsResponse_httpStatus' - The response's http status code.
newGetServiceSettingsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetServiceSettingsResponse
newGetServiceSettingsResponse :: Int -> GetServiceSettingsResponse
newGetServiceSettingsResponse Int
pHttpStatus_ =
  GetServiceSettingsResponse'
    { $sel:homeRegions:GetServiceSettingsResponse' :: Maybe (NonEmpty Text)
homeRegions =
        forall a. Maybe a
Prelude.Nothing,
      $sel:linuxSubscriptionsDiscovery:GetServiceSettingsResponse' :: Maybe LinuxSubscriptionsDiscovery
linuxSubscriptionsDiscovery = forall a. Maybe a
Prelude.Nothing,
      $sel:linuxSubscriptionsDiscoverySettings:GetServiceSettingsResponse' :: Maybe LinuxSubscriptionsDiscoverySettings
linuxSubscriptionsDiscoverySettings =
        forall a. Maybe a
Prelude.Nothing,
      $sel:status:GetServiceSettingsResponse' :: Maybe Status
status = forall a. Maybe a
Prelude.Nothing,
      $sel:statusMessage:GetServiceSettingsResponse' :: Maybe (HashMap Text Text)
statusMessage = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetServiceSettingsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The Region in which License Manager displays the aggregated data for
-- Linux subscriptions.
getServiceSettingsResponse_homeRegions :: Lens.Lens' GetServiceSettingsResponse (Prelude.Maybe (Prelude.NonEmpty Prelude.Text))
getServiceSettingsResponse_homeRegions :: Lens' GetServiceSettingsResponse (Maybe (NonEmpty Text))
getServiceSettingsResponse_homeRegions = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetServiceSettingsResponse' {Maybe (NonEmpty Text)
homeRegions :: Maybe (NonEmpty Text)
$sel:homeRegions:GetServiceSettingsResponse' :: GetServiceSettingsResponse -> Maybe (NonEmpty Text)
homeRegions} -> Maybe (NonEmpty Text)
homeRegions) (\s :: GetServiceSettingsResponse
s@GetServiceSettingsResponse' {} Maybe (NonEmpty Text)
a -> GetServiceSettingsResponse
s {$sel:homeRegions:GetServiceSettingsResponse' :: Maybe (NonEmpty Text)
homeRegions = Maybe (NonEmpty Text)
a} :: GetServiceSettingsResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | Lists if discovery has been enabled for Linux subscriptions.
getServiceSettingsResponse_linuxSubscriptionsDiscovery :: Lens.Lens' GetServiceSettingsResponse (Prelude.Maybe LinuxSubscriptionsDiscovery)
getServiceSettingsResponse_linuxSubscriptionsDiscovery :: Lens'
  GetServiceSettingsResponse (Maybe LinuxSubscriptionsDiscovery)
getServiceSettingsResponse_linuxSubscriptionsDiscovery = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetServiceSettingsResponse' {Maybe LinuxSubscriptionsDiscovery
linuxSubscriptionsDiscovery :: Maybe LinuxSubscriptionsDiscovery
$sel:linuxSubscriptionsDiscovery:GetServiceSettingsResponse' :: GetServiceSettingsResponse -> Maybe LinuxSubscriptionsDiscovery
linuxSubscriptionsDiscovery} -> Maybe LinuxSubscriptionsDiscovery
linuxSubscriptionsDiscovery) (\s :: GetServiceSettingsResponse
s@GetServiceSettingsResponse' {} Maybe LinuxSubscriptionsDiscovery
a -> GetServiceSettingsResponse
s {$sel:linuxSubscriptionsDiscovery:GetServiceSettingsResponse' :: Maybe LinuxSubscriptionsDiscovery
linuxSubscriptionsDiscovery = Maybe LinuxSubscriptionsDiscovery
a} :: GetServiceSettingsResponse)

-- | Lists the settings defined for Linux subscriptions discovery. The
-- settings include if Organizations integration has been enabled, and
-- which Regions data will be aggregated from.
getServiceSettingsResponse_linuxSubscriptionsDiscoverySettings :: Lens.Lens' GetServiceSettingsResponse (Prelude.Maybe LinuxSubscriptionsDiscoverySettings)
getServiceSettingsResponse_linuxSubscriptionsDiscoverySettings :: Lens'
  GetServiceSettingsResponse
  (Maybe LinuxSubscriptionsDiscoverySettings)
getServiceSettingsResponse_linuxSubscriptionsDiscoverySettings = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetServiceSettingsResponse' {Maybe LinuxSubscriptionsDiscoverySettings
linuxSubscriptionsDiscoverySettings :: Maybe LinuxSubscriptionsDiscoverySettings
$sel:linuxSubscriptionsDiscoverySettings:GetServiceSettingsResponse' :: GetServiceSettingsResponse
-> Maybe LinuxSubscriptionsDiscoverySettings
linuxSubscriptionsDiscoverySettings} -> Maybe LinuxSubscriptionsDiscoverySettings
linuxSubscriptionsDiscoverySettings) (\s :: GetServiceSettingsResponse
s@GetServiceSettingsResponse' {} Maybe LinuxSubscriptionsDiscoverySettings
a -> GetServiceSettingsResponse
s {$sel:linuxSubscriptionsDiscoverySettings:GetServiceSettingsResponse' :: Maybe LinuxSubscriptionsDiscoverySettings
linuxSubscriptionsDiscoverySettings = Maybe LinuxSubscriptionsDiscoverySettings
a} :: GetServiceSettingsResponse)

-- | Indicates the status of Linux subscriptions settings being applied.
getServiceSettingsResponse_status :: Lens.Lens' GetServiceSettingsResponse (Prelude.Maybe Status)
getServiceSettingsResponse_status :: Lens' GetServiceSettingsResponse (Maybe Status)
getServiceSettingsResponse_status = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetServiceSettingsResponse' {Maybe Status
status :: Maybe Status
$sel:status:GetServiceSettingsResponse' :: GetServiceSettingsResponse -> Maybe Status
status} -> Maybe Status
status) (\s :: GetServiceSettingsResponse
s@GetServiceSettingsResponse' {} Maybe Status
a -> GetServiceSettingsResponse
s {$sel:status:GetServiceSettingsResponse' :: Maybe Status
status = Maybe Status
a} :: GetServiceSettingsResponse)

-- | A message which details the Linux subscriptions service settings current
-- status.
getServiceSettingsResponse_statusMessage :: Lens.Lens' GetServiceSettingsResponse (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
getServiceSettingsResponse_statusMessage :: Lens' GetServiceSettingsResponse (Maybe (HashMap Text Text))
getServiceSettingsResponse_statusMessage = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetServiceSettingsResponse' {Maybe (HashMap Text Text)
statusMessage :: Maybe (HashMap Text Text)
$sel:statusMessage:GetServiceSettingsResponse' :: GetServiceSettingsResponse -> Maybe (HashMap Text Text)
statusMessage} -> Maybe (HashMap Text Text)
statusMessage) (\s :: GetServiceSettingsResponse
s@GetServiceSettingsResponse' {} Maybe (HashMap Text Text)
a -> GetServiceSettingsResponse
s {$sel:statusMessage:GetServiceSettingsResponse' :: Maybe (HashMap Text Text)
statusMessage = Maybe (HashMap Text Text)
a} :: GetServiceSettingsResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | 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 (NonEmpty Text)
Maybe (HashMap Text Text)
Maybe LinuxSubscriptionsDiscovery
Maybe LinuxSubscriptionsDiscoverySettings
Maybe Status
httpStatus :: Int
statusMessage :: Maybe (HashMap Text Text)
status :: Maybe Status
linuxSubscriptionsDiscoverySettings :: Maybe LinuxSubscriptionsDiscoverySettings
linuxSubscriptionsDiscovery :: Maybe LinuxSubscriptionsDiscovery
homeRegions :: Maybe (NonEmpty Text)
$sel:httpStatus:GetServiceSettingsResponse' :: GetServiceSettingsResponse -> Int
$sel:statusMessage:GetServiceSettingsResponse' :: GetServiceSettingsResponse -> Maybe (HashMap Text Text)
$sel:status:GetServiceSettingsResponse' :: GetServiceSettingsResponse -> Maybe Status
$sel:linuxSubscriptionsDiscoverySettings:GetServiceSettingsResponse' :: GetServiceSettingsResponse
-> Maybe LinuxSubscriptionsDiscoverySettings
$sel:linuxSubscriptionsDiscovery:GetServiceSettingsResponse' :: GetServiceSettingsResponse -> Maybe LinuxSubscriptionsDiscovery
$sel:homeRegions:GetServiceSettingsResponse' :: GetServiceSettingsResponse -> Maybe (NonEmpty Text)
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe (NonEmpty Text)
homeRegions
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe LinuxSubscriptionsDiscovery
linuxSubscriptionsDiscovery
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe LinuxSubscriptionsDiscoverySettings
linuxSubscriptionsDiscoverySettings
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Status
status
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (HashMap Text Text)
statusMessage
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus