{-# 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.GetLicenseConfiguration
-- 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 detailed information about the specified license configuration.
module Amazonka.LicenseManager.GetLicenseConfiguration
  ( -- * Creating a Request
    GetLicenseConfiguration (..),
    newGetLicenseConfiguration,

    -- * Request Lenses
    getLicenseConfiguration_licenseConfigurationArn,

    -- * Destructuring the Response
    GetLicenseConfigurationResponse (..),
    newGetLicenseConfigurationResponse,

    -- * Response Lenses
    getLicenseConfigurationResponse_automatedDiscoveryInformation,
    getLicenseConfigurationResponse_consumedLicenseSummaryList,
    getLicenseConfigurationResponse_consumedLicenses,
    getLicenseConfigurationResponse_description,
    getLicenseConfigurationResponse_disassociateWhenNotFound,
    getLicenseConfigurationResponse_licenseConfigurationArn,
    getLicenseConfigurationResponse_licenseConfigurationId,
    getLicenseConfigurationResponse_licenseCount,
    getLicenseConfigurationResponse_licenseCountHardLimit,
    getLicenseConfigurationResponse_licenseCountingType,
    getLicenseConfigurationResponse_licenseRules,
    getLicenseConfigurationResponse_managedResourceSummaryList,
    getLicenseConfigurationResponse_name,
    getLicenseConfigurationResponse_ownerAccountId,
    getLicenseConfigurationResponse_productInformationList,
    getLicenseConfigurationResponse_status,
    getLicenseConfigurationResponse_tags,
    getLicenseConfigurationResponse_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:/ 'newGetLicenseConfiguration' smart constructor.
data GetLicenseConfiguration = GetLicenseConfiguration'
  { -- | Amazon Resource Name (ARN) of the license configuration.
    GetLicenseConfiguration -> Text
licenseConfigurationArn :: Prelude.Text
  }
  deriving (GetLicenseConfiguration -> GetLicenseConfiguration -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetLicenseConfiguration -> GetLicenseConfiguration -> Bool
$c/= :: GetLicenseConfiguration -> GetLicenseConfiguration -> Bool
== :: GetLicenseConfiguration -> GetLicenseConfiguration -> Bool
$c== :: GetLicenseConfiguration -> GetLicenseConfiguration -> Bool
Prelude.Eq, ReadPrec [GetLicenseConfiguration]
ReadPrec GetLicenseConfiguration
Int -> ReadS GetLicenseConfiguration
ReadS [GetLicenseConfiguration]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetLicenseConfiguration]
$creadListPrec :: ReadPrec [GetLicenseConfiguration]
readPrec :: ReadPrec GetLicenseConfiguration
$creadPrec :: ReadPrec GetLicenseConfiguration
readList :: ReadS [GetLicenseConfiguration]
$creadList :: ReadS [GetLicenseConfiguration]
readsPrec :: Int -> ReadS GetLicenseConfiguration
$creadsPrec :: Int -> ReadS GetLicenseConfiguration
Prelude.Read, Int -> GetLicenseConfiguration -> ShowS
[GetLicenseConfiguration] -> ShowS
GetLicenseConfiguration -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetLicenseConfiguration] -> ShowS
$cshowList :: [GetLicenseConfiguration] -> ShowS
show :: GetLicenseConfiguration -> String
$cshow :: GetLicenseConfiguration -> String
showsPrec :: Int -> GetLicenseConfiguration -> ShowS
$cshowsPrec :: Int -> GetLicenseConfiguration -> ShowS
Prelude.Show, forall x. Rep GetLicenseConfiguration x -> GetLicenseConfiguration
forall x. GetLicenseConfiguration -> Rep GetLicenseConfiguration x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetLicenseConfiguration x -> GetLicenseConfiguration
$cfrom :: forall x. GetLicenseConfiguration -> Rep GetLicenseConfiguration x
Prelude.Generic)

-- |
-- Create a value of 'GetLicenseConfiguration' 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:
--
-- 'licenseConfigurationArn', 'getLicenseConfiguration_licenseConfigurationArn' - Amazon Resource Name (ARN) of the license configuration.
newGetLicenseConfiguration ::
  -- | 'licenseConfigurationArn'
  Prelude.Text ->
  GetLicenseConfiguration
newGetLicenseConfiguration :: Text -> GetLicenseConfiguration
newGetLicenseConfiguration Text
pLicenseConfigurationArn_ =
  GetLicenseConfiguration'
    { $sel:licenseConfigurationArn:GetLicenseConfiguration' :: Text
licenseConfigurationArn =
        Text
pLicenseConfigurationArn_
    }

-- | Amazon Resource Name (ARN) of the license configuration.
getLicenseConfiguration_licenseConfigurationArn :: Lens.Lens' GetLicenseConfiguration Prelude.Text
getLicenseConfiguration_licenseConfigurationArn :: Lens' GetLicenseConfiguration Text
getLicenseConfiguration_licenseConfigurationArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetLicenseConfiguration' {Text
licenseConfigurationArn :: Text
$sel:licenseConfigurationArn:GetLicenseConfiguration' :: GetLicenseConfiguration -> Text
licenseConfigurationArn} -> Text
licenseConfigurationArn) (\s :: GetLicenseConfiguration
s@GetLicenseConfiguration' {} Text
a -> GetLicenseConfiguration
s {$sel:licenseConfigurationArn:GetLicenseConfiguration' :: Text
licenseConfigurationArn = Text
a} :: GetLicenseConfiguration)

instance Core.AWSRequest GetLicenseConfiguration where
  type
    AWSResponse GetLicenseConfiguration =
      GetLicenseConfigurationResponse
  request :: (Service -> Service)
-> GetLicenseConfiguration -> Request GetLicenseConfiguration
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 GetLicenseConfiguration
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse GetLicenseConfiguration)))
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 AutomatedDiscoveryInformation
-> Maybe [ConsumedLicenseSummary]
-> Maybe Integer
-> Maybe Text
-> Maybe Bool
-> Maybe Text
-> Maybe Text
-> Maybe Integer
-> Maybe Bool
-> Maybe LicenseCountingType
-> Maybe [Text]
-> Maybe [ManagedResourceSummary]
-> Maybe Text
-> Maybe Text
-> Maybe [ProductInformation]
-> Maybe Text
-> Maybe [Tag]
-> Int
-> GetLicenseConfigurationResponse
GetLicenseConfigurationResponse'
            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
"AutomatedDiscoveryInformation")
            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
"ConsumedLicenseSummaryList"
                            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.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"ConsumedLicenses")
            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
"Description")
            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
"DisassociateWhenNotFound")
            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
"LicenseConfigurationArn")
            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
"LicenseConfigurationId")
            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
"LicenseCount")
            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
"LicenseCountHardLimit")
            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
"LicenseCountingType")
            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
"LicenseRules" 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.<*> ( Object
x
                            forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"ManagedResourceSummaryList"
                            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.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"Name")
            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
"OwnerAccountId")
            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
"ProductInformationList"
                            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.<*> (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
"Tags" 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 GetLicenseConfiguration where
  hashWithSalt :: Int -> GetLicenseConfiguration -> Int
hashWithSalt Int
_salt GetLicenseConfiguration' {Text
licenseConfigurationArn :: Text
$sel:licenseConfigurationArn:GetLicenseConfiguration' :: GetLicenseConfiguration -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
licenseConfigurationArn

instance Prelude.NFData GetLicenseConfiguration where
  rnf :: GetLicenseConfiguration -> ()
rnf GetLicenseConfiguration' {Text
licenseConfigurationArn :: Text
$sel:licenseConfigurationArn:GetLicenseConfiguration' :: GetLicenseConfiguration -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
licenseConfigurationArn

instance Data.ToHeaders GetLicenseConfiguration where
  toHeaders :: GetLicenseConfiguration -> 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.GetLicenseConfiguration" ::
                          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 GetLicenseConfiguration where
  toJSON :: GetLicenseConfiguration -> Value
toJSON GetLicenseConfiguration' {Text
licenseConfigurationArn :: Text
$sel:licenseConfigurationArn:GetLicenseConfiguration' :: GetLicenseConfiguration -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ forall a. a -> Maybe a
Prelude.Just
              ( Key
"LicenseConfigurationArn"
                  forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
licenseConfigurationArn
              )
          ]
      )

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

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

-- | /See:/ 'newGetLicenseConfigurationResponse' smart constructor.
data GetLicenseConfigurationResponse = GetLicenseConfigurationResponse'
  { -- | Automated discovery information.
    GetLicenseConfigurationResponse
-> Maybe AutomatedDiscoveryInformation
automatedDiscoveryInformation :: Prelude.Maybe AutomatedDiscoveryInformation,
    -- | Summaries of the licenses consumed by resources.
    GetLicenseConfigurationResponse -> Maybe [ConsumedLicenseSummary]
consumedLicenseSummaryList :: Prelude.Maybe [ConsumedLicenseSummary],
    -- | Number of licenses assigned to resources.
    GetLicenseConfigurationResponse -> Maybe Integer
consumedLicenses :: Prelude.Maybe Prelude.Integer,
    -- | Description of the license configuration.
    GetLicenseConfigurationResponse -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    -- | When true, disassociates a resource when software is uninstalled.
    GetLicenseConfigurationResponse -> Maybe Bool
disassociateWhenNotFound :: Prelude.Maybe Prelude.Bool,
    -- | Amazon Resource Name (ARN) of the license configuration.
    GetLicenseConfigurationResponse -> Maybe Text
licenseConfigurationArn :: Prelude.Maybe Prelude.Text,
    -- | Unique ID for the license configuration.
    GetLicenseConfigurationResponse -> Maybe Text
licenseConfigurationId :: Prelude.Maybe Prelude.Text,
    -- | Number of available licenses.
    GetLicenseConfigurationResponse -> Maybe Integer
licenseCount :: Prelude.Maybe Prelude.Integer,
    -- | Sets the number of available licenses as a hard limit.
    GetLicenseConfigurationResponse -> Maybe Bool
licenseCountHardLimit :: Prelude.Maybe Prelude.Bool,
    -- | Dimension for which the licenses are counted.
    GetLicenseConfigurationResponse -> Maybe LicenseCountingType
licenseCountingType :: Prelude.Maybe LicenseCountingType,
    -- | License rules.
    GetLicenseConfigurationResponse -> Maybe [Text]
licenseRules :: Prelude.Maybe [Prelude.Text],
    -- | Summaries of the managed resources.
    GetLicenseConfigurationResponse -> Maybe [ManagedResourceSummary]
managedResourceSummaryList :: Prelude.Maybe [ManagedResourceSummary],
    -- | Name of the license configuration.
    GetLicenseConfigurationResponse -> Maybe Text
name :: Prelude.Maybe Prelude.Text,
    -- | Account ID of the owner of the license configuration.
    GetLicenseConfigurationResponse -> Maybe Text
ownerAccountId :: Prelude.Maybe Prelude.Text,
    -- | Product information.
    GetLicenseConfigurationResponse -> Maybe [ProductInformation]
productInformationList :: Prelude.Maybe [ProductInformation],
    -- | License configuration status.
    GetLicenseConfigurationResponse -> Maybe Text
status :: Prelude.Maybe Prelude.Text,
    -- | Tags for the license configuration.
    GetLicenseConfigurationResponse -> Maybe [Tag]
tags :: Prelude.Maybe [Tag],
    -- | The response's http status code.
    GetLicenseConfigurationResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetLicenseConfigurationResponse
-> GetLicenseConfigurationResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetLicenseConfigurationResponse
-> GetLicenseConfigurationResponse -> Bool
$c/= :: GetLicenseConfigurationResponse
-> GetLicenseConfigurationResponse -> Bool
== :: GetLicenseConfigurationResponse
-> GetLicenseConfigurationResponse -> Bool
$c== :: GetLicenseConfigurationResponse
-> GetLicenseConfigurationResponse -> Bool
Prelude.Eq, ReadPrec [GetLicenseConfigurationResponse]
ReadPrec GetLicenseConfigurationResponse
Int -> ReadS GetLicenseConfigurationResponse
ReadS [GetLicenseConfigurationResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetLicenseConfigurationResponse]
$creadListPrec :: ReadPrec [GetLicenseConfigurationResponse]
readPrec :: ReadPrec GetLicenseConfigurationResponse
$creadPrec :: ReadPrec GetLicenseConfigurationResponse
readList :: ReadS [GetLicenseConfigurationResponse]
$creadList :: ReadS [GetLicenseConfigurationResponse]
readsPrec :: Int -> ReadS GetLicenseConfigurationResponse
$creadsPrec :: Int -> ReadS GetLicenseConfigurationResponse
Prelude.Read, Int -> GetLicenseConfigurationResponse -> ShowS
[GetLicenseConfigurationResponse] -> ShowS
GetLicenseConfigurationResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetLicenseConfigurationResponse] -> ShowS
$cshowList :: [GetLicenseConfigurationResponse] -> ShowS
show :: GetLicenseConfigurationResponse -> String
$cshow :: GetLicenseConfigurationResponse -> String
showsPrec :: Int -> GetLicenseConfigurationResponse -> ShowS
$cshowsPrec :: Int -> GetLicenseConfigurationResponse -> ShowS
Prelude.Show, forall x.
Rep GetLicenseConfigurationResponse x
-> GetLicenseConfigurationResponse
forall x.
GetLicenseConfigurationResponse
-> Rep GetLicenseConfigurationResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetLicenseConfigurationResponse x
-> GetLicenseConfigurationResponse
$cfrom :: forall x.
GetLicenseConfigurationResponse
-> Rep GetLicenseConfigurationResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetLicenseConfigurationResponse' 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:
--
-- 'automatedDiscoveryInformation', 'getLicenseConfigurationResponse_automatedDiscoveryInformation' - Automated discovery information.
--
-- 'consumedLicenseSummaryList', 'getLicenseConfigurationResponse_consumedLicenseSummaryList' - Summaries of the licenses consumed by resources.
--
-- 'consumedLicenses', 'getLicenseConfigurationResponse_consumedLicenses' - Number of licenses assigned to resources.
--
-- 'description', 'getLicenseConfigurationResponse_description' - Description of the license configuration.
--
-- 'disassociateWhenNotFound', 'getLicenseConfigurationResponse_disassociateWhenNotFound' - When true, disassociates a resource when software is uninstalled.
--
-- 'licenseConfigurationArn', 'getLicenseConfigurationResponse_licenseConfigurationArn' - Amazon Resource Name (ARN) of the license configuration.
--
-- 'licenseConfigurationId', 'getLicenseConfigurationResponse_licenseConfigurationId' - Unique ID for the license configuration.
--
-- 'licenseCount', 'getLicenseConfigurationResponse_licenseCount' - Number of available licenses.
--
-- 'licenseCountHardLimit', 'getLicenseConfigurationResponse_licenseCountHardLimit' - Sets the number of available licenses as a hard limit.
--
-- 'licenseCountingType', 'getLicenseConfigurationResponse_licenseCountingType' - Dimension for which the licenses are counted.
--
-- 'licenseRules', 'getLicenseConfigurationResponse_licenseRules' - License rules.
--
-- 'managedResourceSummaryList', 'getLicenseConfigurationResponse_managedResourceSummaryList' - Summaries of the managed resources.
--
-- 'name', 'getLicenseConfigurationResponse_name' - Name of the license configuration.
--
-- 'ownerAccountId', 'getLicenseConfigurationResponse_ownerAccountId' - Account ID of the owner of the license configuration.
--
-- 'productInformationList', 'getLicenseConfigurationResponse_productInformationList' - Product information.
--
-- 'status', 'getLicenseConfigurationResponse_status' - License configuration status.
--
-- 'tags', 'getLicenseConfigurationResponse_tags' - Tags for the license configuration.
--
-- 'httpStatus', 'getLicenseConfigurationResponse_httpStatus' - The response's http status code.
newGetLicenseConfigurationResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetLicenseConfigurationResponse
newGetLicenseConfigurationResponse :: Int -> GetLicenseConfigurationResponse
newGetLicenseConfigurationResponse Int
pHttpStatus_ =
  GetLicenseConfigurationResponse'
    { $sel:automatedDiscoveryInformation:GetLicenseConfigurationResponse' :: Maybe AutomatedDiscoveryInformation
automatedDiscoveryInformation =
        forall a. Maybe a
Prelude.Nothing,
      $sel:consumedLicenseSummaryList:GetLicenseConfigurationResponse' :: Maybe [ConsumedLicenseSummary]
consumedLicenseSummaryList =
        forall a. Maybe a
Prelude.Nothing,
      $sel:consumedLicenses:GetLicenseConfigurationResponse' :: Maybe Integer
consumedLicenses = forall a. Maybe a
Prelude.Nothing,
      $sel:description:GetLicenseConfigurationResponse' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
      $sel:disassociateWhenNotFound:GetLicenseConfigurationResponse' :: Maybe Bool
disassociateWhenNotFound = forall a. Maybe a
Prelude.Nothing,
      $sel:licenseConfigurationArn:GetLicenseConfigurationResponse' :: Maybe Text
licenseConfigurationArn = forall a. Maybe a
Prelude.Nothing,
      $sel:licenseConfigurationId:GetLicenseConfigurationResponse' :: Maybe Text
licenseConfigurationId = forall a. Maybe a
Prelude.Nothing,
      $sel:licenseCount:GetLicenseConfigurationResponse' :: Maybe Integer
licenseCount = forall a. Maybe a
Prelude.Nothing,
      $sel:licenseCountHardLimit:GetLicenseConfigurationResponse' :: Maybe Bool
licenseCountHardLimit = forall a. Maybe a
Prelude.Nothing,
      $sel:licenseCountingType:GetLicenseConfigurationResponse' :: Maybe LicenseCountingType
licenseCountingType = forall a. Maybe a
Prelude.Nothing,
      $sel:licenseRules:GetLicenseConfigurationResponse' :: Maybe [Text]
licenseRules = forall a. Maybe a
Prelude.Nothing,
      $sel:managedResourceSummaryList:GetLicenseConfigurationResponse' :: Maybe [ManagedResourceSummary]
managedResourceSummaryList =
        forall a. Maybe a
Prelude.Nothing,
      $sel:name:GetLicenseConfigurationResponse' :: Maybe Text
name = forall a. Maybe a
Prelude.Nothing,
      $sel:ownerAccountId:GetLicenseConfigurationResponse' :: Maybe Text
ownerAccountId = forall a. Maybe a
Prelude.Nothing,
      $sel:productInformationList:GetLicenseConfigurationResponse' :: Maybe [ProductInformation]
productInformationList = forall a. Maybe a
Prelude.Nothing,
      $sel:status:GetLicenseConfigurationResponse' :: Maybe Text
status = forall a. Maybe a
Prelude.Nothing,
      $sel:tags:GetLicenseConfigurationResponse' :: Maybe [Tag]
tags = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetLicenseConfigurationResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Automated discovery information.
getLicenseConfigurationResponse_automatedDiscoveryInformation :: Lens.Lens' GetLicenseConfigurationResponse (Prelude.Maybe AutomatedDiscoveryInformation)
getLicenseConfigurationResponse_automatedDiscoveryInformation :: Lens'
  GetLicenseConfigurationResponse
  (Maybe AutomatedDiscoveryInformation)
getLicenseConfigurationResponse_automatedDiscoveryInformation = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetLicenseConfigurationResponse' {Maybe AutomatedDiscoveryInformation
automatedDiscoveryInformation :: Maybe AutomatedDiscoveryInformation
$sel:automatedDiscoveryInformation:GetLicenseConfigurationResponse' :: GetLicenseConfigurationResponse
-> Maybe AutomatedDiscoveryInformation
automatedDiscoveryInformation} -> Maybe AutomatedDiscoveryInformation
automatedDiscoveryInformation) (\s :: GetLicenseConfigurationResponse
s@GetLicenseConfigurationResponse' {} Maybe AutomatedDiscoveryInformation
a -> GetLicenseConfigurationResponse
s {$sel:automatedDiscoveryInformation:GetLicenseConfigurationResponse' :: Maybe AutomatedDiscoveryInformation
automatedDiscoveryInformation = Maybe AutomatedDiscoveryInformation
a} :: GetLicenseConfigurationResponse)

-- | Summaries of the licenses consumed by resources.
getLicenseConfigurationResponse_consumedLicenseSummaryList :: Lens.Lens' GetLicenseConfigurationResponse (Prelude.Maybe [ConsumedLicenseSummary])
getLicenseConfigurationResponse_consumedLicenseSummaryList :: Lens'
  GetLicenseConfigurationResponse (Maybe [ConsumedLicenseSummary])
getLicenseConfigurationResponse_consumedLicenseSummaryList = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetLicenseConfigurationResponse' {Maybe [ConsumedLicenseSummary]
consumedLicenseSummaryList :: Maybe [ConsumedLicenseSummary]
$sel:consumedLicenseSummaryList:GetLicenseConfigurationResponse' :: GetLicenseConfigurationResponse -> Maybe [ConsumedLicenseSummary]
consumedLicenseSummaryList} -> Maybe [ConsumedLicenseSummary]
consumedLicenseSummaryList) (\s :: GetLicenseConfigurationResponse
s@GetLicenseConfigurationResponse' {} Maybe [ConsumedLicenseSummary]
a -> GetLicenseConfigurationResponse
s {$sel:consumedLicenseSummaryList:GetLicenseConfigurationResponse' :: Maybe [ConsumedLicenseSummary]
consumedLicenseSummaryList = Maybe [ConsumedLicenseSummary]
a} :: GetLicenseConfigurationResponse) 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

-- | Number of licenses assigned to resources.
getLicenseConfigurationResponse_consumedLicenses :: Lens.Lens' GetLicenseConfigurationResponse (Prelude.Maybe Prelude.Integer)
getLicenseConfigurationResponse_consumedLicenses :: Lens' GetLicenseConfigurationResponse (Maybe Integer)
getLicenseConfigurationResponse_consumedLicenses = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetLicenseConfigurationResponse' {Maybe Integer
consumedLicenses :: Maybe Integer
$sel:consumedLicenses:GetLicenseConfigurationResponse' :: GetLicenseConfigurationResponse -> Maybe Integer
consumedLicenses} -> Maybe Integer
consumedLicenses) (\s :: GetLicenseConfigurationResponse
s@GetLicenseConfigurationResponse' {} Maybe Integer
a -> GetLicenseConfigurationResponse
s {$sel:consumedLicenses:GetLicenseConfigurationResponse' :: Maybe Integer
consumedLicenses = Maybe Integer
a} :: GetLicenseConfigurationResponse)

-- | Description of the license configuration.
getLicenseConfigurationResponse_description :: Lens.Lens' GetLicenseConfigurationResponse (Prelude.Maybe Prelude.Text)
getLicenseConfigurationResponse_description :: Lens' GetLicenseConfigurationResponse (Maybe Text)
getLicenseConfigurationResponse_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetLicenseConfigurationResponse' {Maybe Text
description :: Maybe Text
$sel:description:GetLicenseConfigurationResponse' :: GetLicenseConfigurationResponse -> Maybe Text
description} -> Maybe Text
description) (\s :: GetLicenseConfigurationResponse
s@GetLicenseConfigurationResponse' {} Maybe Text
a -> GetLicenseConfigurationResponse
s {$sel:description:GetLicenseConfigurationResponse' :: Maybe Text
description = Maybe Text
a} :: GetLicenseConfigurationResponse)

-- | When true, disassociates a resource when software is uninstalled.
getLicenseConfigurationResponse_disassociateWhenNotFound :: Lens.Lens' GetLicenseConfigurationResponse (Prelude.Maybe Prelude.Bool)
getLicenseConfigurationResponse_disassociateWhenNotFound :: Lens' GetLicenseConfigurationResponse (Maybe Bool)
getLicenseConfigurationResponse_disassociateWhenNotFound = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetLicenseConfigurationResponse' {Maybe Bool
disassociateWhenNotFound :: Maybe Bool
$sel:disassociateWhenNotFound:GetLicenseConfigurationResponse' :: GetLicenseConfigurationResponse -> Maybe Bool
disassociateWhenNotFound} -> Maybe Bool
disassociateWhenNotFound) (\s :: GetLicenseConfigurationResponse
s@GetLicenseConfigurationResponse' {} Maybe Bool
a -> GetLicenseConfigurationResponse
s {$sel:disassociateWhenNotFound:GetLicenseConfigurationResponse' :: Maybe Bool
disassociateWhenNotFound = Maybe Bool
a} :: GetLicenseConfigurationResponse)

-- | Amazon Resource Name (ARN) of the license configuration.
getLicenseConfigurationResponse_licenseConfigurationArn :: Lens.Lens' GetLicenseConfigurationResponse (Prelude.Maybe Prelude.Text)
getLicenseConfigurationResponse_licenseConfigurationArn :: Lens' GetLicenseConfigurationResponse (Maybe Text)
getLicenseConfigurationResponse_licenseConfigurationArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetLicenseConfigurationResponse' {Maybe Text
licenseConfigurationArn :: Maybe Text
$sel:licenseConfigurationArn:GetLicenseConfigurationResponse' :: GetLicenseConfigurationResponse -> Maybe Text
licenseConfigurationArn} -> Maybe Text
licenseConfigurationArn) (\s :: GetLicenseConfigurationResponse
s@GetLicenseConfigurationResponse' {} Maybe Text
a -> GetLicenseConfigurationResponse
s {$sel:licenseConfigurationArn:GetLicenseConfigurationResponse' :: Maybe Text
licenseConfigurationArn = Maybe Text
a} :: GetLicenseConfigurationResponse)

-- | Unique ID for the license configuration.
getLicenseConfigurationResponse_licenseConfigurationId :: Lens.Lens' GetLicenseConfigurationResponse (Prelude.Maybe Prelude.Text)
getLicenseConfigurationResponse_licenseConfigurationId :: Lens' GetLicenseConfigurationResponse (Maybe Text)
getLicenseConfigurationResponse_licenseConfigurationId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetLicenseConfigurationResponse' {Maybe Text
licenseConfigurationId :: Maybe Text
$sel:licenseConfigurationId:GetLicenseConfigurationResponse' :: GetLicenseConfigurationResponse -> Maybe Text
licenseConfigurationId} -> Maybe Text
licenseConfigurationId) (\s :: GetLicenseConfigurationResponse
s@GetLicenseConfigurationResponse' {} Maybe Text
a -> GetLicenseConfigurationResponse
s {$sel:licenseConfigurationId:GetLicenseConfigurationResponse' :: Maybe Text
licenseConfigurationId = Maybe Text
a} :: GetLicenseConfigurationResponse)

-- | Number of available licenses.
getLicenseConfigurationResponse_licenseCount :: Lens.Lens' GetLicenseConfigurationResponse (Prelude.Maybe Prelude.Integer)
getLicenseConfigurationResponse_licenseCount :: Lens' GetLicenseConfigurationResponse (Maybe Integer)
getLicenseConfigurationResponse_licenseCount = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetLicenseConfigurationResponse' {Maybe Integer
licenseCount :: Maybe Integer
$sel:licenseCount:GetLicenseConfigurationResponse' :: GetLicenseConfigurationResponse -> Maybe Integer
licenseCount} -> Maybe Integer
licenseCount) (\s :: GetLicenseConfigurationResponse
s@GetLicenseConfigurationResponse' {} Maybe Integer
a -> GetLicenseConfigurationResponse
s {$sel:licenseCount:GetLicenseConfigurationResponse' :: Maybe Integer
licenseCount = Maybe Integer
a} :: GetLicenseConfigurationResponse)

-- | Sets the number of available licenses as a hard limit.
getLicenseConfigurationResponse_licenseCountHardLimit :: Lens.Lens' GetLicenseConfigurationResponse (Prelude.Maybe Prelude.Bool)
getLicenseConfigurationResponse_licenseCountHardLimit :: Lens' GetLicenseConfigurationResponse (Maybe Bool)
getLicenseConfigurationResponse_licenseCountHardLimit = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetLicenseConfigurationResponse' {Maybe Bool
licenseCountHardLimit :: Maybe Bool
$sel:licenseCountHardLimit:GetLicenseConfigurationResponse' :: GetLicenseConfigurationResponse -> Maybe Bool
licenseCountHardLimit} -> Maybe Bool
licenseCountHardLimit) (\s :: GetLicenseConfigurationResponse
s@GetLicenseConfigurationResponse' {} Maybe Bool
a -> GetLicenseConfigurationResponse
s {$sel:licenseCountHardLimit:GetLicenseConfigurationResponse' :: Maybe Bool
licenseCountHardLimit = Maybe Bool
a} :: GetLicenseConfigurationResponse)

-- | Dimension for which the licenses are counted.
getLicenseConfigurationResponse_licenseCountingType :: Lens.Lens' GetLicenseConfigurationResponse (Prelude.Maybe LicenseCountingType)
getLicenseConfigurationResponse_licenseCountingType :: Lens' GetLicenseConfigurationResponse (Maybe LicenseCountingType)
getLicenseConfigurationResponse_licenseCountingType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetLicenseConfigurationResponse' {Maybe LicenseCountingType
licenseCountingType :: Maybe LicenseCountingType
$sel:licenseCountingType:GetLicenseConfigurationResponse' :: GetLicenseConfigurationResponse -> Maybe LicenseCountingType
licenseCountingType} -> Maybe LicenseCountingType
licenseCountingType) (\s :: GetLicenseConfigurationResponse
s@GetLicenseConfigurationResponse' {} Maybe LicenseCountingType
a -> GetLicenseConfigurationResponse
s {$sel:licenseCountingType:GetLicenseConfigurationResponse' :: Maybe LicenseCountingType
licenseCountingType = Maybe LicenseCountingType
a} :: GetLicenseConfigurationResponse)

-- | License rules.
getLicenseConfigurationResponse_licenseRules :: Lens.Lens' GetLicenseConfigurationResponse (Prelude.Maybe [Prelude.Text])
getLicenseConfigurationResponse_licenseRules :: Lens' GetLicenseConfigurationResponse (Maybe [Text])
getLicenseConfigurationResponse_licenseRules = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetLicenseConfigurationResponse' {Maybe [Text]
licenseRules :: Maybe [Text]
$sel:licenseRules:GetLicenseConfigurationResponse' :: GetLicenseConfigurationResponse -> Maybe [Text]
licenseRules} -> Maybe [Text]
licenseRules) (\s :: GetLicenseConfigurationResponse
s@GetLicenseConfigurationResponse' {} Maybe [Text]
a -> GetLicenseConfigurationResponse
s {$sel:licenseRules:GetLicenseConfigurationResponse' :: Maybe [Text]
licenseRules = Maybe [Text]
a} :: GetLicenseConfigurationResponse) 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

-- | Summaries of the managed resources.
getLicenseConfigurationResponse_managedResourceSummaryList :: Lens.Lens' GetLicenseConfigurationResponse (Prelude.Maybe [ManagedResourceSummary])
getLicenseConfigurationResponse_managedResourceSummaryList :: Lens'
  GetLicenseConfigurationResponse (Maybe [ManagedResourceSummary])
getLicenseConfigurationResponse_managedResourceSummaryList = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetLicenseConfigurationResponse' {Maybe [ManagedResourceSummary]
managedResourceSummaryList :: Maybe [ManagedResourceSummary]
$sel:managedResourceSummaryList:GetLicenseConfigurationResponse' :: GetLicenseConfigurationResponse -> Maybe [ManagedResourceSummary]
managedResourceSummaryList} -> Maybe [ManagedResourceSummary]
managedResourceSummaryList) (\s :: GetLicenseConfigurationResponse
s@GetLicenseConfigurationResponse' {} Maybe [ManagedResourceSummary]
a -> GetLicenseConfigurationResponse
s {$sel:managedResourceSummaryList:GetLicenseConfigurationResponse' :: Maybe [ManagedResourceSummary]
managedResourceSummaryList = Maybe [ManagedResourceSummary]
a} :: GetLicenseConfigurationResponse) 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

-- | Name of the license configuration.
getLicenseConfigurationResponse_name :: Lens.Lens' GetLicenseConfigurationResponse (Prelude.Maybe Prelude.Text)
getLicenseConfigurationResponse_name :: Lens' GetLicenseConfigurationResponse (Maybe Text)
getLicenseConfigurationResponse_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetLicenseConfigurationResponse' {Maybe Text
name :: Maybe Text
$sel:name:GetLicenseConfigurationResponse' :: GetLicenseConfigurationResponse -> Maybe Text
name} -> Maybe Text
name) (\s :: GetLicenseConfigurationResponse
s@GetLicenseConfigurationResponse' {} Maybe Text
a -> GetLicenseConfigurationResponse
s {$sel:name:GetLicenseConfigurationResponse' :: Maybe Text
name = Maybe Text
a} :: GetLicenseConfigurationResponse)

-- | Account ID of the owner of the license configuration.
getLicenseConfigurationResponse_ownerAccountId :: Lens.Lens' GetLicenseConfigurationResponse (Prelude.Maybe Prelude.Text)
getLicenseConfigurationResponse_ownerAccountId :: Lens' GetLicenseConfigurationResponse (Maybe Text)
getLicenseConfigurationResponse_ownerAccountId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetLicenseConfigurationResponse' {Maybe Text
ownerAccountId :: Maybe Text
$sel:ownerAccountId:GetLicenseConfigurationResponse' :: GetLicenseConfigurationResponse -> Maybe Text
ownerAccountId} -> Maybe Text
ownerAccountId) (\s :: GetLicenseConfigurationResponse
s@GetLicenseConfigurationResponse' {} Maybe Text
a -> GetLicenseConfigurationResponse
s {$sel:ownerAccountId:GetLicenseConfigurationResponse' :: Maybe Text
ownerAccountId = Maybe Text
a} :: GetLicenseConfigurationResponse)

-- | Product information.
getLicenseConfigurationResponse_productInformationList :: Lens.Lens' GetLicenseConfigurationResponse (Prelude.Maybe [ProductInformation])
getLicenseConfigurationResponse_productInformationList :: Lens' GetLicenseConfigurationResponse (Maybe [ProductInformation])
getLicenseConfigurationResponse_productInformationList = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetLicenseConfigurationResponse' {Maybe [ProductInformation]
productInformationList :: Maybe [ProductInformation]
$sel:productInformationList:GetLicenseConfigurationResponse' :: GetLicenseConfigurationResponse -> Maybe [ProductInformation]
productInformationList} -> Maybe [ProductInformation]
productInformationList) (\s :: GetLicenseConfigurationResponse
s@GetLicenseConfigurationResponse' {} Maybe [ProductInformation]
a -> GetLicenseConfigurationResponse
s {$sel:productInformationList:GetLicenseConfigurationResponse' :: Maybe [ProductInformation]
productInformationList = Maybe [ProductInformation]
a} :: GetLicenseConfigurationResponse) 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

-- | License configuration status.
getLicenseConfigurationResponse_status :: Lens.Lens' GetLicenseConfigurationResponse (Prelude.Maybe Prelude.Text)
getLicenseConfigurationResponse_status :: Lens' GetLicenseConfigurationResponse (Maybe Text)
getLicenseConfigurationResponse_status = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetLicenseConfigurationResponse' {Maybe Text
status :: Maybe Text
$sel:status:GetLicenseConfigurationResponse' :: GetLicenseConfigurationResponse -> Maybe Text
status} -> Maybe Text
status) (\s :: GetLicenseConfigurationResponse
s@GetLicenseConfigurationResponse' {} Maybe Text
a -> GetLicenseConfigurationResponse
s {$sel:status:GetLicenseConfigurationResponse' :: Maybe Text
status = Maybe Text
a} :: GetLicenseConfigurationResponse)

-- | Tags for the license configuration.
getLicenseConfigurationResponse_tags :: Lens.Lens' GetLicenseConfigurationResponse (Prelude.Maybe [Tag])
getLicenseConfigurationResponse_tags :: Lens' GetLicenseConfigurationResponse (Maybe [Tag])
getLicenseConfigurationResponse_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetLicenseConfigurationResponse' {Maybe [Tag]
tags :: Maybe [Tag]
$sel:tags:GetLicenseConfigurationResponse' :: GetLicenseConfigurationResponse -> Maybe [Tag]
tags} -> Maybe [Tag]
tags) (\s :: GetLicenseConfigurationResponse
s@GetLicenseConfigurationResponse' {} Maybe [Tag]
a -> GetLicenseConfigurationResponse
s {$sel:tags:GetLicenseConfigurationResponse' :: Maybe [Tag]
tags = Maybe [Tag]
a} :: GetLicenseConfigurationResponse) 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.
getLicenseConfigurationResponse_httpStatus :: Lens.Lens' GetLicenseConfigurationResponse Prelude.Int
getLicenseConfigurationResponse_httpStatus :: Lens' GetLicenseConfigurationResponse Int
getLicenseConfigurationResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetLicenseConfigurationResponse' {Int
httpStatus :: Int
$sel:httpStatus:GetLicenseConfigurationResponse' :: GetLicenseConfigurationResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: GetLicenseConfigurationResponse
s@GetLicenseConfigurationResponse' {} Int
a -> GetLicenseConfigurationResponse
s {$sel:httpStatus:GetLicenseConfigurationResponse' :: Int
httpStatus = Int
a} :: GetLicenseConfigurationResponse)

instance
  Prelude.NFData
    GetLicenseConfigurationResponse
  where
  rnf :: GetLicenseConfigurationResponse -> ()
rnf GetLicenseConfigurationResponse' {Int
Maybe Bool
Maybe Integer
Maybe [Text]
Maybe [ProductInformation]
Maybe [ManagedResourceSummary]
Maybe [ConsumedLicenseSummary]
Maybe [Tag]
Maybe Text
Maybe AutomatedDiscoveryInformation
Maybe LicenseCountingType
httpStatus :: Int
tags :: Maybe [Tag]
status :: Maybe Text
productInformationList :: Maybe [ProductInformation]
ownerAccountId :: Maybe Text
name :: Maybe Text
managedResourceSummaryList :: Maybe [ManagedResourceSummary]
licenseRules :: Maybe [Text]
licenseCountingType :: Maybe LicenseCountingType
licenseCountHardLimit :: Maybe Bool
licenseCount :: Maybe Integer
licenseConfigurationId :: Maybe Text
licenseConfigurationArn :: Maybe Text
disassociateWhenNotFound :: Maybe Bool
description :: Maybe Text
consumedLicenses :: Maybe Integer
consumedLicenseSummaryList :: Maybe [ConsumedLicenseSummary]
automatedDiscoveryInformation :: Maybe AutomatedDiscoveryInformation
$sel:httpStatus:GetLicenseConfigurationResponse' :: GetLicenseConfigurationResponse -> Int
$sel:tags:GetLicenseConfigurationResponse' :: GetLicenseConfigurationResponse -> Maybe [Tag]
$sel:status:GetLicenseConfigurationResponse' :: GetLicenseConfigurationResponse -> Maybe Text
$sel:productInformationList:GetLicenseConfigurationResponse' :: GetLicenseConfigurationResponse -> Maybe [ProductInformation]
$sel:ownerAccountId:GetLicenseConfigurationResponse' :: GetLicenseConfigurationResponse -> Maybe Text
$sel:name:GetLicenseConfigurationResponse' :: GetLicenseConfigurationResponse -> Maybe Text
$sel:managedResourceSummaryList:GetLicenseConfigurationResponse' :: GetLicenseConfigurationResponse -> Maybe [ManagedResourceSummary]
$sel:licenseRules:GetLicenseConfigurationResponse' :: GetLicenseConfigurationResponse -> Maybe [Text]
$sel:licenseCountingType:GetLicenseConfigurationResponse' :: GetLicenseConfigurationResponse -> Maybe LicenseCountingType
$sel:licenseCountHardLimit:GetLicenseConfigurationResponse' :: GetLicenseConfigurationResponse -> Maybe Bool
$sel:licenseCount:GetLicenseConfigurationResponse' :: GetLicenseConfigurationResponse -> Maybe Integer
$sel:licenseConfigurationId:GetLicenseConfigurationResponse' :: GetLicenseConfigurationResponse -> Maybe Text
$sel:licenseConfigurationArn:GetLicenseConfigurationResponse' :: GetLicenseConfigurationResponse -> Maybe Text
$sel:disassociateWhenNotFound:GetLicenseConfigurationResponse' :: GetLicenseConfigurationResponse -> Maybe Bool
$sel:description:GetLicenseConfigurationResponse' :: GetLicenseConfigurationResponse -> Maybe Text
$sel:consumedLicenses:GetLicenseConfigurationResponse' :: GetLicenseConfigurationResponse -> Maybe Integer
$sel:consumedLicenseSummaryList:GetLicenseConfigurationResponse' :: GetLicenseConfigurationResponse -> Maybe [ConsumedLicenseSummary]
$sel:automatedDiscoveryInformation:GetLicenseConfigurationResponse' :: GetLicenseConfigurationResponse
-> Maybe AutomatedDiscoveryInformation
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe AutomatedDiscoveryInformation
automatedDiscoveryInformation
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [ConsumedLicenseSummary]
consumedLicenseSummaryList
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Integer
consumedLicenses
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
description
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
disassociateWhenNotFound
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
licenseConfigurationArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
licenseConfigurationId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Integer
licenseCount
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
licenseCountHardLimit
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe LicenseCountingType
licenseCountingType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
licenseRules
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [ManagedResourceSummary]
managedResourceSummaryList
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
name
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
ownerAccountId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [ProductInformation]
productInformationList
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
status
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Tag]
tags
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus