{-# 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.Greengrass.GetSubscriptionDefinitionVersion
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Retrieves information about a subscription definition version.
module Amazonka.Greengrass.GetSubscriptionDefinitionVersion
  ( -- * Creating a Request
    GetSubscriptionDefinitionVersion (..),
    newGetSubscriptionDefinitionVersion,

    -- * Request Lenses
    getSubscriptionDefinitionVersion_nextToken,
    getSubscriptionDefinitionVersion_subscriptionDefinitionId,
    getSubscriptionDefinitionVersion_subscriptionDefinitionVersionId,

    -- * Destructuring the Response
    GetSubscriptionDefinitionVersionResponse (..),
    newGetSubscriptionDefinitionVersionResponse,

    -- * Response Lenses
    getSubscriptionDefinitionVersionResponse_arn,
    getSubscriptionDefinitionVersionResponse_creationTimestamp,
    getSubscriptionDefinitionVersionResponse_definition,
    getSubscriptionDefinitionVersionResponse_id,
    getSubscriptionDefinitionVersionResponse_nextToken,
    getSubscriptionDefinitionVersionResponse_version,
    getSubscriptionDefinitionVersionResponse_httpStatus,
  )
where

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

-- | /See:/ 'newGetSubscriptionDefinitionVersion' smart constructor.
data GetSubscriptionDefinitionVersion = GetSubscriptionDefinitionVersion'
  { -- | The token for the next set of results, or \'\'null\'\' if there are no
    -- additional results.
    GetSubscriptionDefinitionVersion -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The ID of the subscription definition.
    GetSubscriptionDefinitionVersion -> Text
subscriptionDefinitionId :: Prelude.Text,
    -- | The ID of the subscription definition version. This value maps to the
    -- \'\'Version\'\' property of the corresponding \'\'VersionInformation\'\'
    -- object, which is returned by \'\'ListSubscriptionDefinitionVersions\'\'
    -- requests. If the version is the last one that was associated with a
    -- subscription definition, the value also maps to the
    -- \'\'LatestVersion\'\' property of the corresponding
    -- \'\'DefinitionInformation\'\' object.
    GetSubscriptionDefinitionVersion -> Text
subscriptionDefinitionVersionId :: Prelude.Text
  }
  deriving (GetSubscriptionDefinitionVersion
-> GetSubscriptionDefinitionVersion -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetSubscriptionDefinitionVersion
-> GetSubscriptionDefinitionVersion -> Bool
$c/= :: GetSubscriptionDefinitionVersion
-> GetSubscriptionDefinitionVersion -> Bool
== :: GetSubscriptionDefinitionVersion
-> GetSubscriptionDefinitionVersion -> Bool
$c== :: GetSubscriptionDefinitionVersion
-> GetSubscriptionDefinitionVersion -> Bool
Prelude.Eq, ReadPrec [GetSubscriptionDefinitionVersion]
ReadPrec GetSubscriptionDefinitionVersion
Int -> ReadS GetSubscriptionDefinitionVersion
ReadS [GetSubscriptionDefinitionVersion]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetSubscriptionDefinitionVersion]
$creadListPrec :: ReadPrec [GetSubscriptionDefinitionVersion]
readPrec :: ReadPrec GetSubscriptionDefinitionVersion
$creadPrec :: ReadPrec GetSubscriptionDefinitionVersion
readList :: ReadS [GetSubscriptionDefinitionVersion]
$creadList :: ReadS [GetSubscriptionDefinitionVersion]
readsPrec :: Int -> ReadS GetSubscriptionDefinitionVersion
$creadsPrec :: Int -> ReadS GetSubscriptionDefinitionVersion
Prelude.Read, Int -> GetSubscriptionDefinitionVersion -> ShowS
[GetSubscriptionDefinitionVersion] -> ShowS
GetSubscriptionDefinitionVersion -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetSubscriptionDefinitionVersion] -> ShowS
$cshowList :: [GetSubscriptionDefinitionVersion] -> ShowS
show :: GetSubscriptionDefinitionVersion -> String
$cshow :: GetSubscriptionDefinitionVersion -> String
showsPrec :: Int -> GetSubscriptionDefinitionVersion -> ShowS
$cshowsPrec :: Int -> GetSubscriptionDefinitionVersion -> ShowS
Prelude.Show, forall x.
Rep GetSubscriptionDefinitionVersion x
-> GetSubscriptionDefinitionVersion
forall x.
GetSubscriptionDefinitionVersion
-> Rep GetSubscriptionDefinitionVersion x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetSubscriptionDefinitionVersion x
-> GetSubscriptionDefinitionVersion
$cfrom :: forall x.
GetSubscriptionDefinitionVersion
-> Rep GetSubscriptionDefinitionVersion x
Prelude.Generic)

-- |
-- Create a value of 'GetSubscriptionDefinitionVersion' 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:
--
-- 'nextToken', 'getSubscriptionDefinitionVersion_nextToken' - The token for the next set of results, or \'\'null\'\' if there are no
-- additional results.
--
-- 'subscriptionDefinitionId', 'getSubscriptionDefinitionVersion_subscriptionDefinitionId' - The ID of the subscription definition.
--
-- 'subscriptionDefinitionVersionId', 'getSubscriptionDefinitionVersion_subscriptionDefinitionVersionId' - The ID of the subscription definition version. This value maps to the
-- \'\'Version\'\' property of the corresponding \'\'VersionInformation\'\'
-- object, which is returned by \'\'ListSubscriptionDefinitionVersions\'\'
-- requests. If the version is the last one that was associated with a
-- subscription definition, the value also maps to the
-- \'\'LatestVersion\'\' property of the corresponding
-- \'\'DefinitionInformation\'\' object.
newGetSubscriptionDefinitionVersion ::
  -- | 'subscriptionDefinitionId'
  Prelude.Text ->
  -- | 'subscriptionDefinitionVersionId'
  Prelude.Text ->
  GetSubscriptionDefinitionVersion
newGetSubscriptionDefinitionVersion :: Text -> Text -> GetSubscriptionDefinitionVersion
newGetSubscriptionDefinitionVersion
  Text
pSubscriptionDefinitionId_
  Text
pSubscriptionDefinitionVersionId_ =
    GetSubscriptionDefinitionVersion'
      { $sel:nextToken:GetSubscriptionDefinitionVersion' :: Maybe Text
nextToken =
          forall a. Maybe a
Prelude.Nothing,
        $sel:subscriptionDefinitionId:GetSubscriptionDefinitionVersion' :: Text
subscriptionDefinitionId =
          Text
pSubscriptionDefinitionId_,
        $sel:subscriptionDefinitionVersionId:GetSubscriptionDefinitionVersion' :: Text
subscriptionDefinitionVersionId =
          Text
pSubscriptionDefinitionVersionId_
      }

-- | The token for the next set of results, or \'\'null\'\' if there are no
-- additional results.
getSubscriptionDefinitionVersion_nextToken :: Lens.Lens' GetSubscriptionDefinitionVersion (Prelude.Maybe Prelude.Text)
getSubscriptionDefinitionVersion_nextToken :: Lens' GetSubscriptionDefinitionVersion (Maybe Text)
getSubscriptionDefinitionVersion_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetSubscriptionDefinitionVersion' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:GetSubscriptionDefinitionVersion' :: GetSubscriptionDefinitionVersion -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: GetSubscriptionDefinitionVersion
s@GetSubscriptionDefinitionVersion' {} Maybe Text
a -> GetSubscriptionDefinitionVersion
s {$sel:nextToken:GetSubscriptionDefinitionVersion' :: Maybe Text
nextToken = Maybe Text
a} :: GetSubscriptionDefinitionVersion)

-- | The ID of the subscription definition.
getSubscriptionDefinitionVersion_subscriptionDefinitionId :: Lens.Lens' GetSubscriptionDefinitionVersion Prelude.Text
getSubscriptionDefinitionVersion_subscriptionDefinitionId :: Lens' GetSubscriptionDefinitionVersion Text
getSubscriptionDefinitionVersion_subscriptionDefinitionId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetSubscriptionDefinitionVersion' {Text
subscriptionDefinitionId :: Text
$sel:subscriptionDefinitionId:GetSubscriptionDefinitionVersion' :: GetSubscriptionDefinitionVersion -> Text
subscriptionDefinitionId} -> Text
subscriptionDefinitionId) (\s :: GetSubscriptionDefinitionVersion
s@GetSubscriptionDefinitionVersion' {} Text
a -> GetSubscriptionDefinitionVersion
s {$sel:subscriptionDefinitionId:GetSubscriptionDefinitionVersion' :: Text
subscriptionDefinitionId = Text
a} :: GetSubscriptionDefinitionVersion)

-- | The ID of the subscription definition version. This value maps to the
-- \'\'Version\'\' property of the corresponding \'\'VersionInformation\'\'
-- object, which is returned by \'\'ListSubscriptionDefinitionVersions\'\'
-- requests. If the version is the last one that was associated with a
-- subscription definition, the value also maps to the
-- \'\'LatestVersion\'\' property of the corresponding
-- \'\'DefinitionInformation\'\' object.
getSubscriptionDefinitionVersion_subscriptionDefinitionVersionId :: Lens.Lens' GetSubscriptionDefinitionVersion Prelude.Text
getSubscriptionDefinitionVersion_subscriptionDefinitionVersionId :: Lens' GetSubscriptionDefinitionVersion Text
getSubscriptionDefinitionVersion_subscriptionDefinitionVersionId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetSubscriptionDefinitionVersion' {Text
subscriptionDefinitionVersionId :: Text
$sel:subscriptionDefinitionVersionId:GetSubscriptionDefinitionVersion' :: GetSubscriptionDefinitionVersion -> Text
subscriptionDefinitionVersionId} -> Text
subscriptionDefinitionVersionId) (\s :: GetSubscriptionDefinitionVersion
s@GetSubscriptionDefinitionVersion' {} Text
a -> GetSubscriptionDefinitionVersion
s {$sel:subscriptionDefinitionVersionId:GetSubscriptionDefinitionVersion' :: Text
subscriptionDefinitionVersionId = Text
a} :: GetSubscriptionDefinitionVersion)

instance
  Core.AWSRequest
    GetSubscriptionDefinitionVersion
  where
  type
    AWSResponse GetSubscriptionDefinitionVersion =
      GetSubscriptionDefinitionVersionResponse
  request :: (Service -> Service)
-> GetSubscriptionDefinitionVersion
-> Request GetSubscriptionDefinitionVersion
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 GetSubscriptionDefinitionVersion
-> ClientResponse ClientBody
-> m (Either
        Error
        (ClientResponse (AWSResponse GetSubscriptionDefinitionVersion)))
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 Text
-> Maybe Text
-> Maybe SubscriptionDefinitionVersion
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Int
-> GetSubscriptionDefinitionVersionResponse
GetSubscriptionDefinitionVersionResponse'
            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
"Arn")
            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
"CreationTimestamp")
            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
"Definition")
            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
"Id")
            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
"NextToken")
            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
"Version")
            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
    GetSubscriptionDefinitionVersion
  where
  hashWithSalt :: Int -> GetSubscriptionDefinitionVersion -> Int
hashWithSalt
    Int
_salt
    GetSubscriptionDefinitionVersion' {Maybe Text
Text
subscriptionDefinitionVersionId :: Text
subscriptionDefinitionId :: Text
nextToken :: Maybe Text
$sel:subscriptionDefinitionVersionId:GetSubscriptionDefinitionVersion' :: GetSubscriptionDefinitionVersion -> Text
$sel:subscriptionDefinitionId:GetSubscriptionDefinitionVersion' :: GetSubscriptionDefinitionVersion -> Text
$sel:nextToken:GetSubscriptionDefinitionVersion' :: GetSubscriptionDefinitionVersion -> Maybe Text
..} =
      Int
_salt
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
nextToken
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
subscriptionDefinitionId
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
subscriptionDefinitionVersionId

instance
  Prelude.NFData
    GetSubscriptionDefinitionVersion
  where
  rnf :: GetSubscriptionDefinitionVersion -> ()
rnf GetSubscriptionDefinitionVersion' {Maybe Text
Text
subscriptionDefinitionVersionId :: Text
subscriptionDefinitionId :: Text
nextToken :: Maybe Text
$sel:subscriptionDefinitionVersionId:GetSubscriptionDefinitionVersion' :: GetSubscriptionDefinitionVersion -> Text
$sel:subscriptionDefinitionId:GetSubscriptionDefinitionVersion' :: GetSubscriptionDefinitionVersion -> Text
$sel:nextToken:GetSubscriptionDefinitionVersion' :: GetSubscriptionDefinitionVersion -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
nextToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
subscriptionDefinitionId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
subscriptionDefinitionVersionId

instance
  Data.ToHeaders
    GetSubscriptionDefinitionVersion
  where
  toHeaders :: GetSubscriptionDefinitionVersion -> 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 GetSubscriptionDefinitionVersion where
  toPath :: GetSubscriptionDefinitionVersion -> ByteString
toPath GetSubscriptionDefinitionVersion' {Maybe Text
Text
subscriptionDefinitionVersionId :: Text
subscriptionDefinitionId :: Text
nextToken :: Maybe Text
$sel:subscriptionDefinitionVersionId:GetSubscriptionDefinitionVersion' :: GetSubscriptionDefinitionVersion -> Text
$sel:subscriptionDefinitionId:GetSubscriptionDefinitionVersion' :: GetSubscriptionDefinitionVersion -> Text
$sel:nextToken:GetSubscriptionDefinitionVersion' :: GetSubscriptionDefinitionVersion -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/greengrass/definition/subscriptions/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
subscriptionDefinitionId,
        ByteString
"/versions/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
subscriptionDefinitionVersionId
      ]

instance
  Data.ToQuery
    GetSubscriptionDefinitionVersion
  where
  toQuery :: GetSubscriptionDefinitionVersion -> QueryString
toQuery GetSubscriptionDefinitionVersion' {Maybe Text
Text
subscriptionDefinitionVersionId :: Text
subscriptionDefinitionId :: Text
nextToken :: Maybe Text
$sel:subscriptionDefinitionVersionId:GetSubscriptionDefinitionVersion' :: GetSubscriptionDefinitionVersion -> Text
$sel:subscriptionDefinitionId:GetSubscriptionDefinitionVersion' :: GetSubscriptionDefinitionVersion -> Text
$sel:nextToken:GetSubscriptionDefinitionVersion' :: GetSubscriptionDefinitionVersion -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat [ByteString
"NextToken" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
nextToken]

-- | /See:/ 'newGetSubscriptionDefinitionVersionResponse' smart constructor.
data GetSubscriptionDefinitionVersionResponse = GetSubscriptionDefinitionVersionResponse'
  { -- | The ARN of the subscription definition version.
    GetSubscriptionDefinitionVersionResponse -> Maybe Text
arn :: Prelude.Maybe Prelude.Text,
    -- | The time, in milliseconds since the epoch, when the subscription
    -- definition version was created.
    GetSubscriptionDefinitionVersionResponse -> Maybe Text
creationTimestamp :: Prelude.Maybe Prelude.Text,
    -- | Information about the subscription definition version.
    GetSubscriptionDefinitionVersionResponse
-> Maybe SubscriptionDefinitionVersion
definition :: Prelude.Maybe SubscriptionDefinitionVersion,
    -- | The ID of the subscription definition version.
    GetSubscriptionDefinitionVersionResponse -> Maybe Text
id :: Prelude.Maybe Prelude.Text,
    -- | The token for the next set of results, or \'\'null\'\' if there are no
    -- additional results.
    GetSubscriptionDefinitionVersionResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The version of the subscription definition version.
    GetSubscriptionDefinitionVersionResponse -> Maybe Text
version :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    GetSubscriptionDefinitionVersionResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetSubscriptionDefinitionVersionResponse
-> GetSubscriptionDefinitionVersionResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetSubscriptionDefinitionVersionResponse
-> GetSubscriptionDefinitionVersionResponse -> Bool
$c/= :: GetSubscriptionDefinitionVersionResponse
-> GetSubscriptionDefinitionVersionResponse -> Bool
== :: GetSubscriptionDefinitionVersionResponse
-> GetSubscriptionDefinitionVersionResponse -> Bool
$c== :: GetSubscriptionDefinitionVersionResponse
-> GetSubscriptionDefinitionVersionResponse -> Bool
Prelude.Eq, ReadPrec [GetSubscriptionDefinitionVersionResponse]
ReadPrec GetSubscriptionDefinitionVersionResponse
Int -> ReadS GetSubscriptionDefinitionVersionResponse
ReadS [GetSubscriptionDefinitionVersionResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetSubscriptionDefinitionVersionResponse]
$creadListPrec :: ReadPrec [GetSubscriptionDefinitionVersionResponse]
readPrec :: ReadPrec GetSubscriptionDefinitionVersionResponse
$creadPrec :: ReadPrec GetSubscriptionDefinitionVersionResponse
readList :: ReadS [GetSubscriptionDefinitionVersionResponse]
$creadList :: ReadS [GetSubscriptionDefinitionVersionResponse]
readsPrec :: Int -> ReadS GetSubscriptionDefinitionVersionResponse
$creadsPrec :: Int -> ReadS GetSubscriptionDefinitionVersionResponse
Prelude.Read, Int -> GetSubscriptionDefinitionVersionResponse -> ShowS
[GetSubscriptionDefinitionVersionResponse] -> ShowS
GetSubscriptionDefinitionVersionResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetSubscriptionDefinitionVersionResponse] -> ShowS
$cshowList :: [GetSubscriptionDefinitionVersionResponse] -> ShowS
show :: GetSubscriptionDefinitionVersionResponse -> String
$cshow :: GetSubscriptionDefinitionVersionResponse -> String
showsPrec :: Int -> GetSubscriptionDefinitionVersionResponse -> ShowS
$cshowsPrec :: Int -> GetSubscriptionDefinitionVersionResponse -> ShowS
Prelude.Show, forall x.
Rep GetSubscriptionDefinitionVersionResponse x
-> GetSubscriptionDefinitionVersionResponse
forall x.
GetSubscriptionDefinitionVersionResponse
-> Rep GetSubscriptionDefinitionVersionResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetSubscriptionDefinitionVersionResponse x
-> GetSubscriptionDefinitionVersionResponse
$cfrom :: forall x.
GetSubscriptionDefinitionVersionResponse
-> Rep GetSubscriptionDefinitionVersionResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetSubscriptionDefinitionVersionResponse' 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:
--
-- 'arn', 'getSubscriptionDefinitionVersionResponse_arn' - The ARN of the subscription definition version.
--
-- 'creationTimestamp', 'getSubscriptionDefinitionVersionResponse_creationTimestamp' - The time, in milliseconds since the epoch, when the subscription
-- definition version was created.
--
-- 'definition', 'getSubscriptionDefinitionVersionResponse_definition' - Information about the subscription definition version.
--
-- 'id', 'getSubscriptionDefinitionVersionResponse_id' - The ID of the subscription definition version.
--
-- 'nextToken', 'getSubscriptionDefinitionVersionResponse_nextToken' - The token for the next set of results, or \'\'null\'\' if there are no
-- additional results.
--
-- 'version', 'getSubscriptionDefinitionVersionResponse_version' - The version of the subscription definition version.
--
-- 'httpStatus', 'getSubscriptionDefinitionVersionResponse_httpStatus' - The response's http status code.
newGetSubscriptionDefinitionVersionResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetSubscriptionDefinitionVersionResponse
newGetSubscriptionDefinitionVersionResponse :: Int -> GetSubscriptionDefinitionVersionResponse
newGetSubscriptionDefinitionVersionResponse
  Int
pHttpStatus_ =
    GetSubscriptionDefinitionVersionResponse'
      { $sel:arn:GetSubscriptionDefinitionVersionResponse' :: Maybe Text
arn =
          forall a. Maybe a
Prelude.Nothing,
        $sel:creationTimestamp:GetSubscriptionDefinitionVersionResponse' :: Maybe Text
creationTimestamp =
          forall a. Maybe a
Prelude.Nothing,
        $sel:definition:GetSubscriptionDefinitionVersionResponse' :: Maybe SubscriptionDefinitionVersion
definition = forall a. Maybe a
Prelude.Nothing,
        $sel:id:GetSubscriptionDefinitionVersionResponse' :: Maybe Text
id = forall a. Maybe a
Prelude.Nothing,
        $sel:nextToken:GetSubscriptionDefinitionVersionResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
        $sel:version:GetSubscriptionDefinitionVersionResponse' :: Maybe Text
version = forall a. Maybe a
Prelude.Nothing,
        $sel:httpStatus:GetSubscriptionDefinitionVersionResponse' :: Int
httpStatus = Int
pHttpStatus_
      }

-- | The ARN of the subscription definition version.
getSubscriptionDefinitionVersionResponse_arn :: Lens.Lens' GetSubscriptionDefinitionVersionResponse (Prelude.Maybe Prelude.Text)
getSubscriptionDefinitionVersionResponse_arn :: Lens' GetSubscriptionDefinitionVersionResponse (Maybe Text)
getSubscriptionDefinitionVersionResponse_arn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetSubscriptionDefinitionVersionResponse' {Maybe Text
arn :: Maybe Text
$sel:arn:GetSubscriptionDefinitionVersionResponse' :: GetSubscriptionDefinitionVersionResponse -> Maybe Text
arn} -> Maybe Text
arn) (\s :: GetSubscriptionDefinitionVersionResponse
s@GetSubscriptionDefinitionVersionResponse' {} Maybe Text
a -> GetSubscriptionDefinitionVersionResponse
s {$sel:arn:GetSubscriptionDefinitionVersionResponse' :: Maybe Text
arn = Maybe Text
a} :: GetSubscriptionDefinitionVersionResponse)

-- | The time, in milliseconds since the epoch, when the subscription
-- definition version was created.
getSubscriptionDefinitionVersionResponse_creationTimestamp :: Lens.Lens' GetSubscriptionDefinitionVersionResponse (Prelude.Maybe Prelude.Text)
getSubscriptionDefinitionVersionResponse_creationTimestamp :: Lens' GetSubscriptionDefinitionVersionResponse (Maybe Text)
getSubscriptionDefinitionVersionResponse_creationTimestamp = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetSubscriptionDefinitionVersionResponse' {Maybe Text
creationTimestamp :: Maybe Text
$sel:creationTimestamp:GetSubscriptionDefinitionVersionResponse' :: GetSubscriptionDefinitionVersionResponse -> Maybe Text
creationTimestamp} -> Maybe Text
creationTimestamp) (\s :: GetSubscriptionDefinitionVersionResponse
s@GetSubscriptionDefinitionVersionResponse' {} Maybe Text
a -> GetSubscriptionDefinitionVersionResponse
s {$sel:creationTimestamp:GetSubscriptionDefinitionVersionResponse' :: Maybe Text
creationTimestamp = Maybe Text
a} :: GetSubscriptionDefinitionVersionResponse)

-- | Information about the subscription definition version.
getSubscriptionDefinitionVersionResponse_definition :: Lens.Lens' GetSubscriptionDefinitionVersionResponse (Prelude.Maybe SubscriptionDefinitionVersion)
getSubscriptionDefinitionVersionResponse_definition :: Lens'
  GetSubscriptionDefinitionVersionResponse
  (Maybe SubscriptionDefinitionVersion)
getSubscriptionDefinitionVersionResponse_definition = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetSubscriptionDefinitionVersionResponse' {Maybe SubscriptionDefinitionVersion
definition :: Maybe SubscriptionDefinitionVersion
$sel:definition:GetSubscriptionDefinitionVersionResponse' :: GetSubscriptionDefinitionVersionResponse
-> Maybe SubscriptionDefinitionVersion
definition} -> Maybe SubscriptionDefinitionVersion
definition) (\s :: GetSubscriptionDefinitionVersionResponse
s@GetSubscriptionDefinitionVersionResponse' {} Maybe SubscriptionDefinitionVersion
a -> GetSubscriptionDefinitionVersionResponse
s {$sel:definition:GetSubscriptionDefinitionVersionResponse' :: Maybe SubscriptionDefinitionVersion
definition = Maybe SubscriptionDefinitionVersion
a} :: GetSubscriptionDefinitionVersionResponse)

-- | The ID of the subscription definition version.
getSubscriptionDefinitionVersionResponse_id :: Lens.Lens' GetSubscriptionDefinitionVersionResponse (Prelude.Maybe Prelude.Text)
getSubscriptionDefinitionVersionResponse_id :: Lens' GetSubscriptionDefinitionVersionResponse (Maybe Text)
getSubscriptionDefinitionVersionResponse_id = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetSubscriptionDefinitionVersionResponse' {Maybe Text
id :: Maybe Text
$sel:id:GetSubscriptionDefinitionVersionResponse' :: GetSubscriptionDefinitionVersionResponse -> Maybe Text
id} -> Maybe Text
id) (\s :: GetSubscriptionDefinitionVersionResponse
s@GetSubscriptionDefinitionVersionResponse' {} Maybe Text
a -> GetSubscriptionDefinitionVersionResponse
s {$sel:id:GetSubscriptionDefinitionVersionResponse' :: Maybe Text
id = Maybe Text
a} :: GetSubscriptionDefinitionVersionResponse)

-- | The token for the next set of results, or \'\'null\'\' if there are no
-- additional results.
getSubscriptionDefinitionVersionResponse_nextToken :: Lens.Lens' GetSubscriptionDefinitionVersionResponse (Prelude.Maybe Prelude.Text)
getSubscriptionDefinitionVersionResponse_nextToken :: Lens' GetSubscriptionDefinitionVersionResponse (Maybe Text)
getSubscriptionDefinitionVersionResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetSubscriptionDefinitionVersionResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:GetSubscriptionDefinitionVersionResponse' :: GetSubscriptionDefinitionVersionResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: GetSubscriptionDefinitionVersionResponse
s@GetSubscriptionDefinitionVersionResponse' {} Maybe Text
a -> GetSubscriptionDefinitionVersionResponse
s {$sel:nextToken:GetSubscriptionDefinitionVersionResponse' :: Maybe Text
nextToken = Maybe Text
a} :: GetSubscriptionDefinitionVersionResponse)

-- | The version of the subscription definition version.
getSubscriptionDefinitionVersionResponse_version :: Lens.Lens' GetSubscriptionDefinitionVersionResponse (Prelude.Maybe Prelude.Text)
getSubscriptionDefinitionVersionResponse_version :: Lens' GetSubscriptionDefinitionVersionResponse (Maybe Text)
getSubscriptionDefinitionVersionResponse_version = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetSubscriptionDefinitionVersionResponse' {Maybe Text
version :: Maybe Text
$sel:version:GetSubscriptionDefinitionVersionResponse' :: GetSubscriptionDefinitionVersionResponse -> Maybe Text
version} -> Maybe Text
version) (\s :: GetSubscriptionDefinitionVersionResponse
s@GetSubscriptionDefinitionVersionResponse' {} Maybe Text
a -> GetSubscriptionDefinitionVersionResponse
s {$sel:version:GetSubscriptionDefinitionVersionResponse' :: Maybe Text
version = Maybe Text
a} :: GetSubscriptionDefinitionVersionResponse)

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

instance
  Prelude.NFData
    GetSubscriptionDefinitionVersionResponse
  where
  rnf :: GetSubscriptionDefinitionVersionResponse -> ()
rnf GetSubscriptionDefinitionVersionResponse' {Int
Maybe Text
Maybe SubscriptionDefinitionVersion
httpStatus :: Int
version :: Maybe Text
nextToken :: Maybe Text
id :: Maybe Text
definition :: Maybe SubscriptionDefinitionVersion
creationTimestamp :: Maybe Text
arn :: Maybe Text
$sel:httpStatus:GetSubscriptionDefinitionVersionResponse' :: GetSubscriptionDefinitionVersionResponse -> Int
$sel:version:GetSubscriptionDefinitionVersionResponse' :: GetSubscriptionDefinitionVersionResponse -> Maybe Text
$sel:nextToken:GetSubscriptionDefinitionVersionResponse' :: GetSubscriptionDefinitionVersionResponse -> Maybe Text
$sel:id:GetSubscriptionDefinitionVersionResponse' :: GetSubscriptionDefinitionVersionResponse -> Maybe Text
$sel:definition:GetSubscriptionDefinitionVersionResponse' :: GetSubscriptionDefinitionVersionResponse
-> Maybe SubscriptionDefinitionVersion
$sel:creationTimestamp:GetSubscriptionDefinitionVersionResponse' :: GetSubscriptionDefinitionVersionResponse -> Maybe Text
$sel:arn:GetSubscriptionDefinitionVersionResponse' :: GetSubscriptionDefinitionVersionResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
arn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
creationTimestamp
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe SubscriptionDefinitionVersion
definition
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
id
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
nextToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
version
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus