{-# 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.CloudFormation.DescribeType
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Returns detailed information about an extension that has been
-- registered.
--
-- If you specify a @VersionId@, @DescribeType@ returns information about
-- that specific extension version. Otherwise, it returns information about
-- the default extension version.
module Amazonka.CloudFormation.DescribeType
  ( -- * Creating a Request
    DescribeType (..),
    newDescribeType,

    -- * Request Lenses
    describeType_arn,
    describeType_publicVersionNumber,
    describeType_publisherId,
    describeType_type,
    describeType_typeName,
    describeType_versionId,

    -- * Destructuring the Response
    DescribeTypeResponse (..),
    newDescribeTypeResponse,

    -- * Response Lenses
    describeTypeResponse_arn,
    describeTypeResponse_autoUpdate,
    describeTypeResponse_configurationSchema,
    describeTypeResponse_defaultVersionId,
    describeTypeResponse_deprecatedStatus,
    describeTypeResponse_description,
    describeTypeResponse_documentationUrl,
    describeTypeResponse_executionRoleArn,
    describeTypeResponse_isActivated,
    describeTypeResponse_isDefaultVersion,
    describeTypeResponse_lastUpdated,
    describeTypeResponse_latestPublicVersion,
    describeTypeResponse_loggingConfig,
    describeTypeResponse_originalTypeArn,
    describeTypeResponse_originalTypeName,
    describeTypeResponse_provisioningType,
    describeTypeResponse_publicVersionNumber,
    describeTypeResponse_publisherId,
    describeTypeResponse_requiredActivatedTypes,
    describeTypeResponse_schema,
    describeTypeResponse_sourceUrl,
    describeTypeResponse_timeCreated,
    describeTypeResponse_type,
    describeTypeResponse_typeName,
    describeTypeResponse_typeTestsStatus,
    describeTypeResponse_typeTestsStatusDescription,
    describeTypeResponse_visibility,
    describeTypeResponse_httpStatus,
  )
where

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

-- | /See:/ 'newDescribeType' smart constructor.
data DescribeType = DescribeType'
  { -- | The Amazon Resource Name (ARN) of the extension.
    --
    -- Conditional: You must specify either @TypeName@ and @Type@, or @Arn@.
    DescribeType -> Maybe Text
arn :: Prelude.Maybe Prelude.Text,
    -- | The version number of a public third-party extension.
    DescribeType -> Maybe Text
publicVersionNumber :: Prelude.Maybe Prelude.Text,
    -- | The publisher ID of the extension publisher.
    --
    -- Extensions provided by Amazon Web Services are not assigned a publisher
    -- ID.
    DescribeType -> Maybe Text
publisherId :: Prelude.Maybe Prelude.Text,
    -- | The kind of extension.
    --
    -- Conditional: You must specify either @TypeName@ and @Type@, or @Arn@.
    DescribeType -> Maybe RegistryType
type' :: Prelude.Maybe RegistryType,
    -- | The name of the extension.
    --
    -- Conditional: You must specify either @TypeName@ and @Type@, or @Arn@.
    DescribeType -> Maybe Text
typeName :: Prelude.Maybe Prelude.Text,
    -- | The ID of a specific version of the extension. The version ID is the
    -- value at the end of the Amazon Resource Name (ARN) assigned to the
    -- extension version when it is registered.
    --
    -- If you specify a @VersionId@, @DescribeType@ returns information about
    -- that specific extension version. Otherwise, it returns information about
    -- the default extension version.
    DescribeType -> Maybe Text
versionId :: Prelude.Maybe Prelude.Text
  }
  deriving (DescribeType -> DescribeType -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeType -> DescribeType -> Bool
$c/= :: DescribeType -> DescribeType -> Bool
== :: DescribeType -> DescribeType -> Bool
$c== :: DescribeType -> DescribeType -> Bool
Prelude.Eq, ReadPrec [DescribeType]
ReadPrec DescribeType
Int -> ReadS DescribeType
ReadS [DescribeType]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeType]
$creadListPrec :: ReadPrec [DescribeType]
readPrec :: ReadPrec DescribeType
$creadPrec :: ReadPrec DescribeType
readList :: ReadS [DescribeType]
$creadList :: ReadS [DescribeType]
readsPrec :: Int -> ReadS DescribeType
$creadsPrec :: Int -> ReadS DescribeType
Prelude.Read, Int -> DescribeType -> ShowS
[DescribeType] -> ShowS
DescribeType -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeType] -> ShowS
$cshowList :: [DescribeType] -> ShowS
show :: DescribeType -> String
$cshow :: DescribeType -> String
showsPrec :: Int -> DescribeType -> ShowS
$cshowsPrec :: Int -> DescribeType -> ShowS
Prelude.Show, forall x. Rep DescribeType x -> DescribeType
forall x. DescribeType -> Rep DescribeType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DescribeType x -> DescribeType
$cfrom :: forall x. DescribeType -> Rep DescribeType x
Prelude.Generic)

-- |
-- Create a value of 'DescribeType' 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', 'describeType_arn' - The Amazon Resource Name (ARN) of the extension.
--
-- Conditional: You must specify either @TypeName@ and @Type@, or @Arn@.
--
-- 'publicVersionNumber', 'describeType_publicVersionNumber' - The version number of a public third-party extension.
--
-- 'publisherId', 'describeType_publisherId' - The publisher ID of the extension publisher.
--
-- Extensions provided by Amazon Web Services are not assigned a publisher
-- ID.
--
-- 'type'', 'describeType_type' - The kind of extension.
--
-- Conditional: You must specify either @TypeName@ and @Type@, or @Arn@.
--
-- 'typeName', 'describeType_typeName' - The name of the extension.
--
-- Conditional: You must specify either @TypeName@ and @Type@, or @Arn@.
--
-- 'versionId', 'describeType_versionId' - The ID of a specific version of the extension. The version ID is the
-- value at the end of the Amazon Resource Name (ARN) assigned to the
-- extension version when it is registered.
--
-- If you specify a @VersionId@, @DescribeType@ returns information about
-- that specific extension version. Otherwise, it returns information about
-- the default extension version.
newDescribeType ::
  DescribeType
newDescribeType :: DescribeType
newDescribeType =
  DescribeType'
    { $sel:arn:DescribeType' :: Maybe Text
arn = forall a. Maybe a
Prelude.Nothing,
      $sel:publicVersionNumber:DescribeType' :: Maybe Text
publicVersionNumber = forall a. Maybe a
Prelude.Nothing,
      $sel:publisherId:DescribeType' :: Maybe Text
publisherId = forall a. Maybe a
Prelude.Nothing,
      $sel:type':DescribeType' :: Maybe RegistryType
type' = forall a. Maybe a
Prelude.Nothing,
      $sel:typeName:DescribeType' :: Maybe Text
typeName = forall a. Maybe a
Prelude.Nothing,
      $sel:versionId:DescribeType' :: Maybe Text
versionId = forall a. Maybe a
Prelude.Nothing
    }

-- | The Amazon Resource Name (ARN) of the extension.
--
-- Conditional: You must specify either @TypeName@ and @Type@, or @Arn@.
describeType_arn :: Lens.Lens' DescribeType (Prelude.Maybe Prelude.Text)
describeType_arn :: Lens' DescribeType (Maybe Text)
describeType_arn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeType' {Maybe Text
arn :: Maybe Text
$sel:arn:DescribeType' :: DescribeType -> Maybe Text
arn} -> Maybe Text
arn) (\s :: DescribeType
s@DescribeType' {} Maybe Text
a -> DescribeType
s {$sel:arn:DescribeType' :: Maybe Text
arn = Maybe Text
a} :: DescribeType)

-- | The version number of a public third-party extension.
describeType_publicVersionNumber :: Lens.Lens' DescribeType (Prelude.Maybe Prelude.Text)
describeType_publicVersionNumber :: Lens' DescribeType (Maybe Text)
describeType_publicVersionNumber = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeType' {Maybe Text
publicVersionNumber :: Maybe Text
$sel:publicVersionNumber:DescribeType' :: DescribeType -> Maybe Text
publicVersionNumber} -> Maybe Text
publicVersionNumber) (\s :: DescribeType
s@DescribeType' {} Maybe Text
a -> DescribeType
s {$sel:publicVersionNumber:DescribeType' :: Maybe Text
publicVersionNumber = Maybe Text
a} :: DescribeType)

-- | The publisher ID of the extension publisher.
--
-- Extensions provided by Amazon Web Services are not assigned a publisher
-- ID.
describeType_publisherId :: Lens.Lens' DescribeType (Prelude.Maybe Prelude.Text)
describeType_publisherId :: Lens' DescribeType (Maybe Text)
describeType_publisherId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeType' {Maybe Text
publisherId :: Maybe Text
$sel:publisherId:DescribeType' :: DescribeType -> Maybe Text
publisherId} -> Maybe Text
publisherId) (\s :: DescribeType
s@DescribeType' {} Maybe Text
a -> DescribeType
s {$sel:publisherId:DescribeType' :: Maybe Text
publisherId = Maybe Text
a} :: DescribeType)

-- | The kind of extension.
--
-- Conditional: You must specify either @TypeName@ and @Type@, or @Arn@.
describeType_type :: Lens.Lens' DescribeType (Prelude.Maybe RegistryType)
describeType_type :: Lens' DescribeType (Maybe RegistryType)
describeType_type = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeType' {Maybe RegistryType
type' :: Maybe RegistryType
$sel:type':DescribeType' :: DescribeType -> Maybe RegistryType
type'} -> Maybe RegistryType
type') (\s :: DescribeType
s@DescribeType' {} Maybe RegistryType
a -> DescribeType
s {$sel:type':DescribeType' :: Maybe RegistryType
type' = Maybe RegistryType
a} :: DescribeType)

-- | The name of the extension.
--
-- Conditional: You must specify either @TypeName@ and @Type@, or @Arn@.
describeType_typeName :: Lens.Lens' DescribeType (Prelude.Maybe Prelude.Text)
describeType_typeName :: Lens' DescribeType (Maybe Text)
describeType_typeName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeType' {Maybe Text
typeName :: Maybe Text
$sel:typeName:DescribeType' :: DescribeType -> Maybe Text
typeName} -> Maybe Text
typeName) (\s :: DescribeType
s@DescribeType' {} Maybe Text
a -> DescribeType
s {$sel:typeName:DescribeType' :: Maybe Text
typeName = Maybe Text
a} :: DescribeType)

-- | The ID of a specific version of the extension. The version ID is the
-- value at the end of the Amazon Resource Name (ARN) assigned to the
-- extension version when it is registered.
--
-- If you specify a @VersionId@, @DescribeType@ returns information about
-- that specific extension version. Otherwise, it returns information about
-- the default extension version.
describeType_versionId :: Lens.Lens' DescribeType (Prelude.Maybe Prelude.Text)
describeType_versionId :: Lens' DescribeType (Maybe Text)
describeType_versionId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeType' {Maybe Text
versionId :: Maybe Text
$sel:versionId:DescribeType' :: DescribeType -> Maybe Text
versionId} -> Maybe Text
versionId) (\s :: DescribeType
s@DescribeType' {} Maybe Text
a -> DescribeType
s {$sel:versionId:DescribeType' :: Maybe Text
versionId = Maybe Text
a} :: DescribeType)

instance Core.AWSRequest DescribeType where
  type AWSResponse DescribeType = DescribeTypeResponse
  request :: (Service -> Service) -> DescribeType -> Request DescribeType
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.postQuery (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy DescribeType
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse DescribeType)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
Text
-> (Int
    -> ResponseHeaders -> [Node] -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveXMLWrapper
      Text
"DescribeTypeResult"
      ( \Int
s ResponseHeaders
h [Node]
x ->
          Maybe Text
-> Maybe Bool
-> Maybe Text
-> Maybe Text
-> Maybe DeprecatedStatus
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Bool
-> Maybe Bool
-> Maybe ISO8601
-> Maybe Text
-> Maybe LoggingConfig
-> Maybe Text
-> Maybe Text
-> Maybe ProvisioningType
-> Maybe Text
-> Maybe Text
-> Maybe [RequiredActivatedType]
-> Maybe Text
-> Maybe Text
-> Maybe ISO8601
-> Maybe RegistryType
-> Maybe Text
-> Maybe TypeTestsStatus
-> Maybe Text
-> Maybe Visibility
-> Int
-> DescribeTypeResponse
DescribeTypeResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"Arn")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"AutoUpdate")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"ConfigurationSchema")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"DefaultVersionId")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"DeprecatedStatus")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"Description")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"DocumentationUrl")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"ExecutionRoleArn")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"IsActivated")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"IsDefaultVersion")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"LastUpdated")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"LatestPublicVersion")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"LoggingConfig")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"OriginalTypeArn")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"OriginalTypeName")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"ProvisioningType")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"PublicVersionNumber")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"PublisherId")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ( [Node]
x
                            forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"RequiredActivatedTypes"
                            forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                            forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
Prelude.>>= forall (f :: * -> *) a b.
Applicative f =>
([a] -> f b) -> [a] -> f (Maybe b)
Core.may (forall a. FromXML a => Text -> [Node] -> Either String [a]
Data.parseXMLList Text
"member")
                        )
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"Schema")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"SourceUrl")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"TimeCreated")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"Type")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"TypeName")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"TypeTestsStatus")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"TypeTestsStatusDescription")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"Visibility")
            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 DescribeType where
  hashWithSalt :: Int -> DescribeType -> Int
hashWithSalt Int
_salt DescribeType' {Maybe Text
Maybe RegistryType
versionId :: Maybe Text
typeName :: Maybe Text
type' :: Maybe RegistryType
publisherId :: Maybe Text
publicVersionNumber :: Maybe Text
arn :: Maybe Text
$sel:versionId:DescribeType' :: DescribeType -> Maybe Text
$sel:typeName:DescribeType' :: DescribeType -> Maybe Text
$sel:type':DescribeType' :: DescribeType -> Maybe RegistryType
$sel:publisherId:DescribeType' :: DescribeType -> Maybe Text
$sel:publicVersionNumber:DescribeType' :: DescribeType -> Maybe Text
$sel:arn:DescribeType' :: DescribeType -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
arn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
publicVersionNumber
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
publisherId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe RegistryType
type'
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
typeName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
versionId

instance Prelude.NFData DescribeType where
  rnf :: DescribeType -> ()
rnf DescribeType' {Maybe Text
Maybe RegistryType
versionId :: Maybe Text
typeName :: Maybe Text
type' :: Maybe RegistryType
publisherId :: Maybe Text
publicVersionNumber :: Maybe Text
arn :: Maybe Text
$sel:versionId:DescribeType' :: DescribeType -> Maybe Text
$sel:typeName:DescribeType' :: DescribeType -> Maybe Text
$sel:type':DescribeType' :: DescribeType -> Maybe RegistryType
$sel:publisherId:DescribeType' :: DescribeType -> Maybe Text
$sel:publicVersionNumber:DescribeType' :: DescribeType -> Maybe Text
$sel:arn:DescribeType' :: DescribeType -> 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
publicVersionNumber
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
publisherId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe RegistryType
type'
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
typeName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
versionId

instance Data.ToHeaders DescribeType where
  toHeaders :: DescribeType -> ResponseHeaders
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

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

instance Data.ToQuery DescribeType where
  toQuery :: DescribeType -> QueryString
toQuery DescribeType' {Maybe Text
Maybe RegistryType
versionId :: Maybe Text
typeName :: Maybe Text
type' :: Maybe RegistryType
publisherId :: Maybe Text
publicVersionNumber :: Maybe Text
arn :: Maybe Text
$sel:versionId:DescribeType' :: DescribeType -> Maybe Text
$sel:typeName:DescribeType' :: DescribeType -> Maybe Text
$sel:type':DescribeType' :: DescribeType -> Maybe RegistryType
$sel:publisherId:DescribeType' :: DescribeType -> Maybe Text
$sel:publicVersionNumber:DescribeType' :: DescribeType -> Maybe Text
$sel:arn:DescribeType' :: DescribeType -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"DescribeType" :: Prelude.ByteString),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2010-05-15" :: Prelude.ByteString),
        ByteString
"Arn" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
arn,
        ByteString
"PublicVersionNumber" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
publicVersionNumber,
        ByteString
"PublisherId" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
publisherId,
        ByteString
"Type" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe RegistryType
type',
        ByteString
"TypeName" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
typeName,
        ByteString
"VersionId" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
versionId
      ]

-- | /See:/ 'newDescribeTypeResponse' smart constructor.
data DescribeTypeResponse = DescribeTypeResponse'
  { -- | The Amazon Resource Name (ARN) of the extension.
    DescribeTypeResponse -> Maybe Text
arn :: Prelude.Maybe Prelude.Text,
    -- | Whether CloudFormation automatically updates the extension in this
    -- account and region when a new /minor/ version is published by the
    -- extension publisher. Major versions released by the publisher must be
    -- manually updated. For more information, see
    -- <AWSCloudFormation/latest/UserGuide/registry-public.html#registry-public-enable Activating public extensions for use in your account>
    -- in the /CloudFormation User Guide/.
    DescribeTypeResponse -> Maybe Bool
autoUpdate :: Prelude.Maybe Prelude.Bool,
    -- | A JSON string that represent the current configuration data for the
    -- extension in this account and region.
    --
    -- To set the configuration data for an extension, use
    -- <https://docs.aws.amazon.com/AWSCloudFormation/latest/APIReference/API_SetTypeConfiguration.html SetTypeConfiguration>.
    -- For more information, see
    -- <https://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/registry-register.html#registry-set-configuration Configuring extensions at the account level>
    -- in the /CloudFormation User Guide/.
    DescribeTypeResponse -> Maybe Text
configurationSchema :: Prelude.Maybe Prelude.Text,
    -- | The ID of the default version of the extension. The default version is
    -- used when the extension version isn\'t specified.
    --
    -- This applies only to private extensions you have registered in your
    -- account. For public extensions, both those provided by Amazon Web
    -- Services and published by third parties, CloudFormation returns @null@.
    -- For more information, see
    -- <https://docs.aws.amazon.com/AWSCloudFormation/latest/APIReference/API_RegisterType.html RegisterType>.
    --
    -- To set the default version of an extension, use
    -- @ @@SetTypeDefaultVersion@@ @.
    DescribeTypeResponse -> Maybe Text
defaultVersionId :: Prelude.Maybe Prelude.Text,
    -- | The deprecation status of the extension version.
    --
    -- Valid values include:
    --
    -- -   @LIVE@: The extension is activated or registered and can be used in
    --     CloudFormation operations, dependent on its provisioning behavior
    --     and visibility scope.
    --
    -- -   @DEPRECATED@: The extension has been deactivated or deregistered and
    --     can no longer be used in CloudFormation operations.
    --
    -- For public third-party extensions, CloudFormation returns @null@.
    DescribeTypeResponse -> Maybe DeprecatedStatus
deprecatedStatus :: Prelude.Maybe DeprecatedStatus,
    -- | The description of the extension.
    DescribeTypeResponse -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    -- | The URL of a page providing detailed documentation for this extension.
    DescribeTypeResponse -> Maybe Text
documentationUrl :: Prelude.Maybe Prelude.Text,
    -- | The Amazon Resource Name (ARN) of the IAM execution role used to
    -- register the extension. This applies only to private extensions you have
    -- registered in your account. For more information, see
    -- <https://docs.aws.amazon.com/AWSCloudFormation/latest/APIReference/API_RegisterType.html RegisterType>.
    --
    -- If the registered extension calls any Amazon Web Services APIs, you must
    -- create an
    -- /<https://docs.aws.amazon.com/IAM/latest/UserGuide/id_roles.html IAM execution role>/
    -- that includes the necessary permissions to call those Amazon Web
    -- Services APIs, and provision that execution role in your account.
    -- CloudFormation then assumes that execution role to provide your
    -- extension with the appropriate credentials.
    DescribeTypeResponse -> Maybe Text
executionRoleArn :: Prelude.Maybe Prelude.Text,
    -- | Whether the extension is activated in the account and region.
    --
    -- This only applies to public third-party extensions. For all other
    -- extensions, CloudFormation returns @null@.
    DescribeTypeResponse -> Maybe Bool
isActivated :: Prelude.Maybe Prelude.Bool,
    -- | Whether the specified extension version is set as the default version.
    --
    -- This applies only to private extensions you have registered in your
    -- account, and extensions published by Amazon Web Services. For public
    -- third-party extensions, whether they are activated in your account,
    -- CloudFormation returns @null@.
    DescribeTypeResponse -> Maybe Bool
isDefaultVersion :: Prelude.Maybe Prelude.Bool,
    -- | When the specified extension version was registered. This applies only
    -- to:
    --
    -- -   Private extensions you have registered in your account. For more
    --     information, see
    --     <https://docs.aws.amazon.com/AWSCloudFormation/latest/APIReference/API_RegisterType.html RegisterType>.
    --
    -- -   Public extensions you have activated in your account with
    --     auto-update specified. For more information, see
    --     <https://docs.aws.amazon.com/AWSCloudFormation/latest/APIReference/API_ActivateType.html ActivateType>.
    DescribeTypeResponse -> Maybe ISO8601
lastUpdated :: Prelude.Maybe Data.ISO8601,
    -- | The latest version of a public extension /that is available/ for use.
    --
    -- This only applies if you specify a public extension, and you don\'t
    -- specify a version. For all other requests, CloudFormation returns
    -- @null@.
    DescribeTypeResponse -> Maybe Text
latestPublicVersion :: Prelude.Maybe Prelude.Text,
    -- | Contains logging configuration information for private extensions. This
    -- applies only to private extensions you have registered in your account.
    -- For public extensions, both those provided by Amazon Web Services and
    -- published by third parties, CloudFormation returns @null@. For more
    -- information, see
    -- <https://docs.aws.amazon.com/AWSCloudFormation/latest/APIReference/API_RegisterType.html RegisterType>.
    DescribeTypeResponse -> Maybe LoggingConfig
loggingConfig :: Prelude.Maybe LoggingConfig,
    -- | For public extensions that have been activated for this account and
    -- region, the Amazon Resource Name (ARN) of the public extension.
    DescribeTypeResponse -> Maybe Text
originalTypeArn :: Prelude.Maybe Prelude.Text,
    -- | For public extensions that have been activated for this account and
    -- region, the type name of the public extension.
    --
    -- If you specified a @TypeNameAlias@ when enabling the extension in this
    -- account and region, CloudFormation treats that alias as the extension\'s
    -- type name within the account and region, not the type name of the public
    -- extension. For more information, see
    -- <https://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/registry-public.html#registry-public-enable-alias Specifying aliases to refer to extensions>
    -- in the /CloudFormation User Guide/.
    DescribeTypeResponse -> Maybe Text
originalTypeName :: Prelude.Maybe Prelude.Text,
    -- | For resource type extensions, the provisioning behavior of the resource
    -- type. CloudFormation determines the provisioning type during
    -- registration, based on the types of handlers in the schema handler
    -- package submitted.
    --
    -- Valid values include:
    --
    -- -   @FULLY_MUTABLE@: The resource type includes an update handler to
    --     process updates to the type during stack update operations.
    --
    -- -   @IMMUTABLE@: The resource type doesn\'t include an update handler,
    --     so the type can\'t be updated and must instead be replaced during
    --     stack update operations.
    --
    -- -   @NON_PROVISIONABLE@: The resource type doesn\'t include all the
    --     following handlers, and therefore can\'t actually be provisioned.
    --
    --     -   create
    --
    --     -   read
    --
    --     -   delete
    DescribeTypeResponse -> Maybe ProvisioningType
provisioningType :: Prelude.Maybe ProvisioningType,
    -- | The version number of a public third-party extension.
    --
    -- This applies only if you specify a public extension you have activated
    -- in your account, or specify a public extension without specifying a
    -- version. For all other extensions, CloudFormation returns @null@.
    DescribeTypeResponse -> Maybe Text
publicVersionNumber :: Prelude.Maybe Prelude.Text,
    -- | The publisher ID of the extension publisher.
    --
    -- This applies only to public third-party extensions. For private
    -- registered extensions, and extensions provided by Amazon Web Services,
    -- CloudFormation returns @null@.
    DescribeTypeResponse -> Maybe Text
publisherId :: Prelude.Maybe Prelude.Text,
    -- | For extensions that are modules, the public third-party extensions that
    -- must be activated in your account in order for the module itself to be
    -- activated.
    DescribeTypeResponse -> Maybe [RequiredActivatedType]
requiredActivatedTypes :: Prelude.Maybe [RequiredActivatedType],
    -- | The schema that defines the extension.
    --
    -- For more information about extension schemas, see
    -- <https://docs.aws.amazon.com/cloudformation-cli/latest/userguide/resource-type-schema.html Resource Provider Schema>
    -- in the /CloudFormation CLI User Guide/.
    DescribeTypeResponse -> Maybe Text
schema :: Prelude.Maybe Prelude.Text,
    -- | The URL of the source code for the extension.
    DescribeTypeResponse -> Maybe Text
sourceUrl :: Prelude.Maybe Prelude.Text,
    -- | When the specified private extension version was registered or activated
    -- in your account.
    DescribeTypeResponse -> Maybe ISO8601
timeCreated :: Prelude.Maybe Data.ISO8601,
    -- | The kind of extension.
    DescribeTypeResponse -> Maybe RegistryType
type' :: Prelude.Maybe RegistryType,
    -- | The name of the extension.
    --
    -- If the extension is a public third-party type you have activated with a
    -- type name alias, CloudFormation returns the type name alias. For more
    -- information, see
    -- <https://docs.aws.amazon.com/AWSCloudFormation/latest/APIReference/API_ActivateType.html ActivateType>.
    DescribeTypeResponse -> Maybe Text
typeName :: Prelude.Maybe Prelude.Text,
    -- | The contract test status of the registered extension version. To return
    -- the extension test status of a specific extension version, you must
    -- specify @VersionId@.
    --
    -- This applies only to registered private extension versions.
    -- CloudFormation doesn\'t return this information for public extensions,
    -- whether they are activated in your account.
    --
    -- -   @PASSED@: The extension has passed all its contract tests.
    --
    --     An extension must have a test status of @PASSED@ before it can be
    --     published. For more information, see
    --     <https://docs.aws.amazon.com/cloudformation-cli/latest/userguide/resource-type-publish.html Publishing extensions to make them available for public use>
    --     in the /CloudFormation Command Line Interface User Guide/.
    --
    -- -   @FAILED@: The extension has failed one or more contract tests.
    --
    -- -   @IN_PROGRESS@: Contract tests are currently being performed on the
    --     extension.
    --
    -- -   @NOT_TESTED@: Contract tests haven\'t been performed on the
    --     extension.
    DescribeTypeResponse -> Maybe TypeTestsStatus
typeTestsStatus :: Prelude.Maybe TypeTestsStatus,
    -- | The description of the test status. To return the extension test status
    -- of a specific extension version, you must specify @VersionId@.
    --
    -- This applies only to registered private extension versions.
    -- CloudFormation doesn\'t return this information for public extensions,
    -- whether they are activated in your account.
    DescribeTypeResponse -> Maybe Text
typeTestsStatusDescription :: Prelude.Maybe Prelude.Text,
    -- | The scope at which the extension is visible and usable in CloudFormation
    -- operations.
    --
    -- Valid values include:
    --
    -- -   @PRIVATE@: The extension is only visible and usable within the
    --     account in which it is registered. CloudFormation marks any
    --     extensions you register as @PRIVATE@.
    --
    -- -   @PUBLIC@: The extension is publicly visible and usable within any
    --     Amazon Web Services account.
    DescribeTypeResponse -> Maybe Visibility
visibility :: Prelude.Maybe Visibility,
    -- | The response's http status code.
    DescribeTypeResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DescribeTypeResponse -> DescribeTypeResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeTypeResponse -> DescribeTypeResponse -> Bool
$c/= :: DescribeTypeResponse -> DescribeTypeResponse -> Bool
== :: DescribeTypeResponse -> DescribeTypeResponse -> Bool
$c== :: DescribeTypeResponse -> DescribeTypeResponse -> Bool
Prelude.Eq, ReadPrec [DescribeTypeResponse]
ReadPrec DescribeTypeResponse
Int -> ReadS DescribeTypeResponse
ReadS [DescribeTypeResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeTypeResponse]
$creadListPrec :: ReadPrec [DescribeTypeResponse]
readPrec :: ReadPrec DescribeTypeResponse
$creadPrec :: ReadPrec DescribeTypeResponse
readList :: ReadS [DescribeTypeResponse]
$creadList :: ReadS [DescribeTypeResponse]
readsPrec :: Int -> ReadS DescribeTypeResponse
$creadsPrec :: Int -> ReadS DescribeTypeResponse
Prelude.Read, Int -> DescribeTypeResponse -> ShowS
[DescribeTypeResponse] -> ShowS
DescribeTypeResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeTypeResponse] -> ShowS
$cshowList :: [DescribeTypeResponse] -> ShowS
show :: DescribeTypeResponse -> String
$cshow :: DescribeTypeResponse -> String
showsPrec :: Int -> DescribeTypeResponse -> ShowS
$cshowsPrec :: Int -> DescribeTypeResponse -> ShowS
Prelude.Show, forall x. Rep DescribeTypeResponse x -> DescribeTypeResponse
forall x. DescribeTypeResponse -> Rep DescribeTypeResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DescribeTypeResponse x -> DescribeTypeResponse
$cfrom :: forall x. DescribeTypeResponse -> Rep DescribeTypeResponse x
Prelude.Generic)

-- |
-- Create a value of 'DescribeTypeResponse' 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', 'describeTypeResponse_arn' - The Amazon Resource Name (ARN) of the extension.
--
-- 'autoUpdate', 'describeTypeResponse_autoUpdate' - Whether CloudFormation automatically updates the extension in this
-- account and region when a new /minor/ version is published by the
-- extension publisher. Major versions released by the publisher must be
-- manually updated. For more information, see
-- <AWSCloudFormation/latest/UserGuide/registry-public.html#registry-public-enable Activating public extensions for use in your account>
-- in the /CloudFormation User Guide/.
--
-- 'configurationSchema', 'describeTypeResponse_configurationSchema' - A JSON string that represent the current configuration data for the
-- extension in this account and region.
--
-- To set the configuration data for an extension, use
-- <https://docs.aws.amazon.com/AWSCloudFormation/latest/APIReference/API_SetTypeConfiguration.html SetTypeConfiguration>.
-- For more information, see
-- <https://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/registry-register.html#registry-set-configuration Configuring extensions at the account level>
-- in the /CloudFormation User Guide/.
--
-- 'defaultVersionId', 'describeTypeResponse_defaultVersionId' - The ID of the default version of the extension. The default version is
-- used when the extension version isn\'t specified.
--
-- This applies only to private extensions you have registered in your
-- account. For public extensions, both those provided by Amazon Web
-- Services and published by third parties, CloudFormation returns @null@.
-- For more information, see
-- <https://docs.aws.amazon.com/AWSCloudFormation/latest/APIReference/API_RegisterType.html RegisterType>.
--
-- To set the default version of an extension, use
-- @ @@SetTypeDefaultVersion@@ @.
--
-- 'deprecatedStatus', 'describeTypeResponse_deprecatedStatus' - The deprecation status of the extension version.
--
-- Valid values include:
--
-- -   @LIVE@: The extension is activated or registered and can be used in
--     CloudFormation operations, dependent on its provisioning behavior
--     and visibility scope.
--
-- -   @DEPRECATED@: The extension has been deactivated or deregistered and
--     can no longer be used in CloudFormation operations.
--
-- For public third-party extensions, CloudFormation returns @null@.
--
-- 'description', 'describeTypeResponse_description' - The description of the extension.
--
-- 'documentationUrl', 'describeTypeResponse_documentationUrl' - The URL of a page providing detailed documentation for this extension.
--
-- 'executionRoleArn', 'describeTypeResponse_executionRoleArn' - The Amazon Resource Name (ARN) of the IAM execution role used to
-- register the extension. This applies only to private extensions you have
-- registered in your account. For more information, see
-- <https://docs.aws.amazon.com/AWSCloudFormation/latest/APIReference/API_RegisterType.html RegisterType>.
--
-- If the registered extension calls any Amazon Web Services APIs, you must
-- create an
-- /<https://docs.aws.amazon.com/IAM/latest/UserGuide/id_roles.html IAM execution role>/
-- that includes the necessary permissions to call those Amazon Web
-- Services APIs, and provision that execution role in your account.
-- CloudFormation then assumes that execution role to provide your
-- extension with the appropriate credentials.
--
-- 'isActivated', 'describeTypeResponse_isActivated' - Whether the extension is activated in the account and region.
--
-- This only applies to public third-party extensions. For all other
-- extensions, CloudFormation returns @null@.
--
-- 'isDefaultVersion', 'describeTypeResponse_isDefaultVersion' - Whether the specified extension version is set as the default version.
--
-- This applies only to private extensions you have registered in your
-- account, and extensions published by Amazon Web Services. For public
-- third-party extensions, whether they are activated in your account,
-- CloudFormation returns @null@.
--
-- 'lastUpdated', 'describeTypeResponse_lastUpdated' - When the specified extension version was registered. This applies only
-- to:
--
-- -   Private extensions you have registered in your account. For more
--     information, see
--     <https://docs.aws.amazon.com/AWSCloudFormation/latest/APIReference/API_RegisterType.html RegisterType>.
--
-- -   Public extensions you have activated in your account with
--     auto-update specified. For more information, see
--     <https://docs.aws.amazon.com/AWSCloudFormation/latest/APIReference/API_ActivateType.html ActivateType>.
--
-- 'latestPublicVersion', 'describeTypeResponse_latestPublicVersion' - The latest version of a public extension /that is available/ for use.
--
-- This only applies if you specify a public extension, and you don\'t
-- specify a version. For all other requests, CloudFormation returns
-- @null@.
--
-- 'loggingConfig', 'describeTypeResponse_loggingConfig' - Contains logging configuration information for private extensions. This
-- applies only to private extensions you have registered in your account.
-- For public extensions, both those provided by Amazon Web Services and
-- published by third parties, CloudFormation returns @null@. For more
-- information, see
-- <https://docs.aws.amazon.com/AWSCloudFormation/latest/APIReference/API_RegisterType.html RegisterType>.
--
-- 'originalTypeArn', 'describeTypeResponse_originalTypeArn' - For public extensions that have been activated for this account and
-- region, the Amazon Resource Name (ARN) of the public extension.
--
-- 'originalTypeName', 'describeTypeResponse_originalTypeName' - For public extensions that have been activated for this account and
-- region, the type name of the public extension.
--
-- If you specified a @TypeNameAlias@ when enabling the extension in this
-- account and region, CloudFormation treats that alias as the extension\'s
-- type name within the account and region, not the type name of the public
-- extension. For more information, see
-- <https://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/registry-public.html#registry-public-enable-alias Specifying aliases to refer to extensions>
-- in the /CloudFormation User Guide/.
--
-- 'provisioningType', 'describeTypeResponse_provisioningType' - For resource type extensions, the provisioning behavior of the resource
-- type. CloudFormation determines the provisioning type during
-- registration, based on the types of handlers in the schema handler
-- package submitted.
--
-- Valid values include:
--
-- -   @FULLY_MUTABLE@: The resource type includes an update handler to
--     process updates to the type during stack update operations.
--
-- -   @IMMUTABLE@: The resource type doesn\'t include an update handler,
--     so the type can\'t be updated and must instead be replaced during
--     stack update operations.
--
-- -   @NON_PROVISIONABLE@: The resource type doesn\'t include all the
--     following handlers, and therefore can\'t actually be provisioned.
--
--     -   create
--
--     -   read
--
--     -   delete
--
-- 'publicVersionNumber', 'describeTypeResponse_publicVersionNumber' - The version number of a public third-party extension.
--
-- This applies only if you specify a public extension you have activated
-- in your account, or specify a public extension without specifying a
-- version. For all other extensions, CloudFormation returns @null@.
--
-- 'publisherId', 'describeTypeResponse_publisherId' - The publisher ID of the extension publisher.
--
-- This applies only to public third-party extensions. For private
-- registered extensions, and extensions provided by Amazon Web Services,
-- CloudFormation returns @null@.
--
-- 'requiredActivatedTypes', 'describeTypeResponse_requiredActivatedTypes' - For extensions that are modules, the public third-party extensions that
-- must be activated in your account in order for the module itself to be
-- activated.
--
-- 'schema', 'describeTypeResponse_schema' - The schema that defines the extension.
--
-- For more information about extension schemas, see
-- <https://docs.aws.amazon.com/cloudformation-cli/latest/userguide/resource-type-schema.html Resource Provider Schema>
-- in the /CloudFormation CLI User Guide/.
--
-- 'sourceUrl', 'describeTypeResponse_sourceUrl' - The URL of the source code for the extension.
--
-- 'timeCreated', 'describeTypeResponse_timeCreated' - When the specified private extension version was registered or activated
-- in your account.
--
-- 'type'', 'describeTypeResponse_type' - The kind of extension.
--
-- 'typeName', 'describeTypeResponse_typeName' - The name of the extension.
--
-- If the extension is a public third-party type you have activated with a
-- type name alias, CloudFormation returns the type name alias. For more
-- information, see
-- <https://docs.aws.amazon.com/AWSCloudFormation/latest/APIReference/API_ActivateType.html ActivateType>.
--
-- 'typeTestsStatus', 'describeTypeResponse_typeTestsStatus' - The contract test status of the registered extension version. To return
-- the extension test status of a specific extension version, you must
-- specify @VersionId@.
--
-- This applies only to registered private extension versions.
-- CloudFormation doesn\'t return this information for public extensions,
-- whether they are activated in your account.
--
-- -   @PASSED@: The extension has passed all its contract tests.
--
--     An extension must have a test status of @PASSED@ before it can be
--     published. For more information, see
--     <https://docs.aws.amazon.com/cloudformation-cli/latest/userguide/resource-type-publish.html Publishing extensions to make them available for public use>
--     in the /CloudFormation Command Line Interface User Guide/.
--
-- -   @FAILED@: The extension has failed one or more contract tests.
--
-- -   @IN_PROGRESS@: Contract tests are currently being performed on the
--     extension.
--
-- -   @NOT_TESTED@: Contract tests haven\'t been performed on the
--     extension.
--
-- 'typeTestsStatusDescription', 'describeTypeResponse_typeTestsStatusDescription' - The description of the test status. To return the extension test status
-- of a specific extension version, you must specify @VersionId@.
--
-- This applies only to registered private extension versions.
-- CloudFormation doesn\'t return this information for public extensions,
-- whether they are activated in your account.
--
-- 'visibility', 'describeTypeResponse_visibility' - The scope at which the extension is visible and usable in CloudFormation
-- operations.
--
-- Valid values include:
--
-- -   @PRIVATE@: The extension is only visible and usable within the
--     account in which it is registered. CloudFormation marks any
--     extensions you register as @PRIVATE@.
--
-- -   @PUBLIC@: The extension is publicly visible and usable within any
--     Amazon Web Services account.
--
-- 'httpStatus', 'describeTypeResponse_httpStatus' - The response's http status code.
newDescribeTypeResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DescribeTypeResponse
newDescribeTypeResponse :: Int -> DescribeTypeResponse
newDescribeTypeResponse Int
pHttpStatus_ =
  DescribeTypeResponse'
    { $sel:arn:DescribeTypeResponse' :: Maybe Text
arn = forall a. Maybe a
Prelude.Nothing,
      $sel:autoUpdate:DescribeTypeResponse' :: Maybe Bool
autoUpdate = forall a. Maybe a
Prelude.Nothing,
      $sel:configurationSchema:DescribeTypeResponse' :: Maybe Text
configurationSchema = forall a. Maybe a
Prelude.Nothing,
      $sel:defaultVersionId:DescribeTypeResponse' :: Maybe Text
defaultVersionId = forall a. Maybe a
Prelude.Nothing,
      $sel:deprecatedStatus:DescribeTypeResponse' :: Maybe DeprecatedStatus
deprecatedStatus = forall a. Maybe a
Prelude.Nothing,
      $sel:description:DescribeTypeResponse' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
      $sel:documentationUrl:DescribeTypeResponse' :: Maybe Text
documentationUrl = forall a. Maybe a
Prelude.Nothing,
      $sel:executionRoleArn:DescribeTypeResponse' :: Maybe Text
executionRoleArn = forall a. Maybe a
Prelude.Nothing,
      $sel:isActivated:DescribeTypeResponse' :: Maybe Bool
isActivated = forall a. Maybe a
Prelude.Nothing,
      $sel:isDefaultVersion:DescribeTypeResponse' :: Maybe Bool
isDefaultVersion = forall a. Maybe a
Prelude.Nothing,
      $sel:lastUpdated:DescribeTypeResponse' :: Maybe ISO8601
lastUpdated = forall a. Maybe a
Prelude.Nothing,
      $sel:latestPublicVersion:DescribeTypeResponse' :: Maybe Text
latestPublicVersion = forall a. Maybe a
Prelude.Nothing,
      $sel:loggingConfig:DescribeTypeResponse' :: Maybe LoggingConfig
loggingConfig = forall a. Maybe a
Prelude.Nothing,
      $sel:originalTypeArn:DescribeTypeResponse' :: Maybe Text
originalTypeArn = forall a. Maybe a
Prelude.Nothing,
      $sel:originalTypeName:DescribeTypeResponse' :: Maybe Text
originalTypeName = forall a. Maybe a
Prelude.Nothing,
      $sel:provisioningType:DescribeTypeResponse' :: Maybe ProvisioningType
provisioningType = forall a. Maybe a
Prelude.Nothing,
      $sel:publicVersionNumber:DescribeTypeResponse' :: Maybe Text
publicVersionNumber = forall a. Maybe a
Prelude.Nothing,
      $sel:publisherId:DescribeTypeResponse' :: Maybe Text
publisherId = forall a. Maybe a
Prelude.Nothing,
      $sel:requiredActivatedTypes:DescribeTypeResponse' :: Maybe [RequiredActivatedType]
requiredActivatedTypes = forall a. Maybe a
Prelude.Nothing,
      $sel:schema:DescribeTypeResponse' :: Maybe Text
schema = forall a. Maybe a
Prelude.Nothing,
      $sel:sourceUrl:DescribeTypeResponse' :: Maybe Text
sourceUrl = forall a. Maybe a
Prelude.Nothing,
      $sel:timeCreated:DescribeTypeResponse' :: Maybe ISO8601
timeCreated = forall a. Maybe a
Prelude.Nothing,
      $sel:type':DescribeTypeResponse' :: Maybe RegistryType
type' = forall a. Maybe a
Prelude.Nothing,
      $sel:typeName:DescribeTypeResponse' :: Maybe Text
typeName = forall a. Maybe a
Prelude.Nothing,
      $sel:typeTestsStatus:DescribeTypeResponse' :: Maybe TypeTestsStatus
typeTestsStatus = forall a. Maybe a
Prelude.Nothing,
      $sel:typeTestsStatusDescription:DescribeTypeResponse' :: Maybe Text
typeTestsStatusDescription = forall a. Maybe a
Prelude.Nothing,
      $sel:visibility:DescribeTypeResponse' :: Maybe Visibility
visibility = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DescribeTypeResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The Amazon Resource Name (ARN) of the extension.
describeTypeResponse_arn :: Lens.Lens' DescribeTypeResponse (Prelude.Maybe Prelude.Text)
describeTypeResponse_arn :: Lens' DescribeTypeResponse (Maybe Text)
describeTypeResponse_arn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeTypeResponse' {Maybe Text
arn :: Maybe Text
$sel:arn:DescribeTypeResponse' :: DescribeTypeResponse -> Maybe Text
arn} -> Maybe Text
arn) (\s :: DescribeTypeResponse
s@DescribeTypeResponse' {} Maybe Text
a -> DescribeTypeResponse
s {$sel:arn:DescribeTypeResponse' :: Maybe Text
arn = Maybe Text
a} :: DescribeTypeResponse)

-- | Whether CloudFormation automatically updates the extension in this
-- account and region when a new /minor/ version is published by the
-- extension publisher. Major versions released by the publisher must be
-- manually updated. For more information, see
-- <AWSCloudFormation/latest/UserGuide/registry-public.html#registry-public-enable Activating public extensions for use in your account>
-- in the /CloudFormation User Guide/.
describeTypeResponse_autoUpdate :: Lens.Lens' DescribeTypeResponse (Prelude.Maybe Prelude.Bool)
describeTypeResponse_autoUpdate :: Lens' DescribeTypeResponse (Maybe Bool)
describeTypeResponse_autoUpdate = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeTypeResponse' {Maybe Bool
autoUpdate :: Maybe Bool
$sel:autoUpdate:DescribeTypeResponse' :: DescribeTypeResponse -> Maybe Bool
autoUpdate} -> Maybe Bool
autoUpdate) (\s :: DescribeTypeResponse
s@DescribeTypeResponse' {} Maybe Bool
a -> DescribeTypeResponse
s {$sel:autoUpdate:DescribeTypeResponse' :: Maybe Bool
autoUpdate = Maybe Bool
a} :: DescribeTypeResponse)

-- | A JSON string that represent the current configuration data for the
-- extension in this account and region.
--
-- To set the configuration data for an extension, use
-- <https://docs.aws.amazon.com/AWSCloudFormation/latest/APIReference/API_SetTypeConfiguration.html SetTypeConfiguration>.
-- For more information, see
-- <https://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/registry-register.html#registry-set-configuration Configuring extensions at the account level>
-- in the /CloudFormation User Guide/.
describeTypeResponse_configurationSchema :: Lens.Lens' DescribeTypeResponse (Prelude.Maybe Prelude.Text)
describeTypeResponse_configurationSchema :: Lens' DescribeTypeResponse (Maybe Text)
describeTypeResponse_configurationSchema = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeTypeResponse' {Maybe Text
configurationSchema :: Maybe Text
$sel:configurationSchema:DescribeTypeResponse' :: DescribeTypeResponse -> Maybe Text
configurationSchema} -> Maybe Text
configurationSchema) (\s :: DescribeTypeResponse
s@DescribeTypeResponse' {} Maybe Text
a -> DescribeTypeResponse
s {$sel:configurationSchema:DescribeTypeResponse' :: Maybe Text
configurationSchema = Maybe Text
a} :: DescribeTypeResponse)

-- | The ID of the default version of the extension. The default version is
-- used when the extension version isn\'t specified.
--
-- This applies only to private extensions you have registered in your
-- account. For public extensions, both those provided by Amazon Web
-- Services and published by third parties, CloudFormation returns @null@.
-- For more information, see
-- <https://docs.aws.amazon.com/AWSCloudFormation/latest/APIReference/API_RegisterType.html RegisterType>.
--
-- To set the default version of an extension, use
-- @ @@SetTypeDefaultVersion@@ @.
describeTypeResponse_defaultVersionId :: Lens.Lens' DescribeTypeResponse (Prelude.Maybe Prelude.Text)
describeTypeResponse_defaultVersionId :: Lens' DescribeTypeResponse (Maybe Text)
describeTypeResponse_defaultVersionId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeTypeResponse' {Maybe Text
defaultVersionId :: Maybe Text
$sel:defaultVersionId:DescribeTypeResponse' :: DescribeTypeResponse -> Maybe Text
defaultVersionId} -> Maybe Text
defaultVersionId) (\s :: DescribeTypeResponse
s@DescribeTypeResponse' {} Maybe Text
a -> DescribeTypeResponse
s {$sel:defaultVersionId:DescribeTypeResponse' :: Maybe Text
defaultVersionId = Maybe Text
a} :: DescribeTypeResponse)

-- | The deprecation status of the extension version.
--
-- Valid values include:
--
-- -   @LIVE@: The extension is activated or registered and can be used in
--     CloudFormation operations, dependent on its provisioning behavior
--     and visibility scope.
--
-- -   @DEPRECATED@: The extension has been deactivated or deregistered and
--     can no longer be used in CloudFormation operations.
--
-- For public third-party extensions, CloudFormation returns @null@.
describeTypeResponse_deprecatedStatus :: Lens.Lens' DescribeTypeResponse (Prelude.Maybe DeprecatedStatus)
describeTypeResponse_deprecatedStatus :: Lens' DescribeTypeResponse (Maybe DeprecatedStatus)
describeTypeResponse_deprecatedStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeTypeResponse' {Maybe DeprecatedStatus
deprecatedStatus :: Maybe DeprecatedStatus
$sel:deprecatedStatus:DescribeTypeResponse' :: DescribeTypeResponse -> Maybe DeprecatedStatus
deprecatedStatus} -> Maybe DeprecatedStatus
deprecatedStatus) (\s :: DescribeTypeResponse
s@DescribeTypeResponse' {} Maybe DeprecatedStatus
a -> DescribeTypeResponse
s {$sel:deprecatedStatus:DescribeTypeResponse' :: Maybe DeprecatedStatus
deprecatedStatus = Maybe DeprecatedStatus
a} :: DescribeTypeResponse)

-- | The description of the extension.
describeTypeResponse_description :: Lens.Lens' DescribeTypeResponse (Prelude.Maybe Prelude.Text)
describeTypeResponse_description :: Lens' DescribeTypeResponse (Maybe Text)
describeTypeResponse_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeTypeResponse' {Maybe Text
description :: Maybe Text
$sel:description:DescribeTypeResponse' :: DescribeTypeResponse -> Maybe Text
description} -> Maybe Text
description) (\s :: DescribeTypeResponse
s@DescribeTypeResponse' {} Maybe Text
a -> DescribeTypeResponse
s {$sel:description:DescribeTypeResponse' :: Maybe Text
description = Maybe Text
a} :: DescribeTypeResponse)

-- | The URL of a page providing detailed documentation for this extension.
describeTypeResponse_documentationUrl :: Lens.Lens' DescribeTypeResponse (Prelude.Maybe Prelude.Text)
describeTypeResponse_documentationUrl :: Lens' DescribeTypeResponse (Maybe Text)
describeTypeResponse_documentationUrl = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeTypeResponse' {Maybe Text
documentationUrl :: Maybe Text
$sel:documentationUrl:DescribeTypeResponse' :: DescribeTypeResponse -> Maybe Text
documentationUrl} -> Maybe Text
documentationUrl) (\s :: DescribeTypeResponse
s@DescribeTypeResponse' {} Maybe Text
a -> DescribeTypeResponse
s {$sel:documentationUrl:DescribeTypeResponse' :: Maybe Text
documentationUrl = Maybe Text
a} :: DescribeTypeResponse)

-- | The Amazon Resource Name (ARN) of the IAM execution role used to
-- register the extension. This applies only to private extensions you have
-- registered in your account. For more information, see
-- <https://docs.aws.amazon.com/AWSCloudFormation/latest/APIReference/API_RegisterType.html RegisterType>.
--
-- If the registered extension calls any Amazon Web Services APIs, you must
-- create an
-- /<https://docs.aws.amazon.com/IAM/latest/UserGuide/id_roles.html IAM execution role>/
-- that includes the necessary permissions to call those Amazon Web
-- Services APIs, and provision that execution role in your account.
-- CloudFormation then assumes that execution role to provide your
-- extension with the appropriate credentials.
describeTypeResponse_executionRoleArn :: Lens.Lens' DescribeTypeResponse (Prelude.Maybe Prelude.Text)
describeTypeResponse_executionRoleArn :: Lens' DescribeTypeResponse (Maybe Text)
describeTypeResponse_executionRoleArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeTypeResponse' {Maybe Text
executionRoleArn :: Maybe Text
$sel:executionRoleArn:DescribeTypeResponse' :: DescribeTypeResponse -> Maybe Text
executionRoleArn} -> Maybe Text
executionRoleArn) (\s :: DescribeTypeResponse
s@DescribeTypeResponse' {} Maybe Text
a -> DescribeTypeResponse
s {$sel:executionRoleArn:DescribeTypeResponse' :: Maybe Text
executionRoleArn = Maybe Text
a} :: DescribeTypeResponse)

-- | Whether the extension is activated in the account and region.
--
-- This only applies to public third-party extensions. For all other
-- extensions, CloudFormation returns @null@.
describeTypeResponse_isActivated :: Lens.Lens' DescribeTypeResponse (Prelude.Maybe Prelude.Bool)
describeTypeResponse_isActivated :: Lens' DescribeTypeResponse (Maybe Bool)
describeTypeResponse_isActivated = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeTypeResponse' {Maybe Bool
isActivated :: Maybe Bool
$sel:isActivated:DescribeTypeResponse' :: DescribeTypeResponse -> Maybe Bool
isActivated} -> Maybe Bool
isActivated) (\s :: DescribeTypeResponse
s@DescribeTypeResponse' {} Maybe Bool
a -> DescribeTypeResponse
s {$sel:isActivated:DescribeTypeResponse' :: Maybe Bool
isActivated = Maybe Bool
a} :: DescribeTypeResponse)

-- | Whether the specified extension version is set as the default version.
--
-- This applies only to private extensions you have registered in your
-- account, and extensions published by Amazon Web Services. For public
-- third-party extensions, whether they are activated in your account,
-- CloudFormation returns @null@.
describeTypeResponse_isDefaultVersion :: Lens.Lens' DescribeTypeResponse (Prelude.Maybe Prelude.Bool)
describeTypeResponse_isDefaultVersion :: Lens' DescribeTypeResponse (Maybe Bool)
describeTypeResponse_isDefaultVersion = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeTypeResponse' {Maybe Bool
isDefaultVersion :: Maybe Bool
$sel:isDefaultVersion:DescribeTypeResponse' :: DescribeTypeResponse -> Maybe Bool
isDefaultVersion} -> Maybe Bool
isDefaultVersion) (\s :: DescribeTypeResponse
s@DescribeTypeResponse' {} Maybe Bool
a -> DescribeTypeResponse
s {$sel:isDefaultVersion:DescribeTypeResponse' :: Maybe Bool
isDefaultVersion = Maybe Bool
a} :: DescribeTypeResponse)

-- | When the specified extension version was registered. This applies only
-- to:
--
-- -   Private extensions you have registered in your account. For more
--     information, see
--     <https://docs.aws.amazon.com/AWSCloudFormation/latest/APIReference/API_RegisterType.html RegisterType>.
--
-- -   Public extensions you have activated in your account with
--     auto-update specified. For more information, see
--     <https://docs.aws.amazon.com/AWSCloudFormation/latest/APIReference/API_ActivateType.html ActivateType>.
describeTypeResponse_lastUpdated :: Lens.Lens' DescribeTypeResponse (Prelude.Maybe Prelude.UTCTime)
describeTypeResponse_lastUpdated :: Lens' DescribeTypeResponse (Maybe UTCTime)
describeTypeResponse_lastUpdated = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeTypeResponse' {Maybe ISO8601
lastUpdated :: Maybe ISO8601
$sel:lastUpdated:DescribeTypeResponse' :: DescribeTypeResponse -> Maybe ISO8601
lastUpdated} -> Maybe ISO8601
lastUpdated) (\s :: DescribeTypeResponse
s@DescribeTypeResponse' {} Maybe ISO8601
a -> DescribeTypeResponse
s {$sel:lastUpdated:DescribeTypeResponse' :: Maybe ISO8601
lastUpdated = Maybe ISO8601
a} :: DescribeTypeResponse) 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 (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | The latest version of a public extension /that is available/ for use.
--
-- This only applies if you specify a public extension, and you don\'t
-- specify a version. For all other requests, CloudFormation returns
-- @null@.
describeTypeResponse_latestPublicVersion :: Lens.Lens' DescribeTypeResponse (Prelude.Maybe Prelude.Text)
describeTypeResponse_latestPublicVersion :: Lens' DescribeTypeResponse (Maybe Text)
describeTypeResponse_latestPublicVersion = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeTypeResponse' {Maybe Text
latestPublicVersion :: Maybe Text
$sel:latestPublicVersion:DescribeTypeResponse' :: DescribeTypeResponse -> Maybe Text
latestPublicVersion} -> Maybe Text
latestPublicVersion) (\s :: DescribeTypeResponse
s@DescribeTypeResponse' {} Maybe Text
a -> DescribeTypeResponse
s {$sel:latestPublicVersion:DescribeTypeResponse' :: Maybe Text
latestPublicVersion = Maybe Text
a} :: DescribeTypeResponse)

-- | Contains logging configuration information for private extensions. This
-- applies only to private extensions you have registered in your account.
-- For public extensions, both those provided by Amazon Web Services and
-- published by third parties, CloudFormation returns @null@. For more
-- information, see
-- <https://docs.aws.amazon.com/AWSCloudFormation/latest/APIReference/API_RegisterType.html RegisterType>.
describeTypeResponse_loggingConfig :: Lens.Lens' DescribeTypeResponse (Prelude.Maybe LoggingConfig)
describeTypeResponse_loggingConfig :: Lens' DescribeTypeResponse (Maybe LoggingConfig)
describeTypeResponse_loggingConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeTypeResponse' {Maybe LoggingConfig
loggingConfig :: Maybe LoggingConfig
$sel:loggingConfig:DescribeTypeResponse' :: DescribeTypeResponse -> Maybe LoggingConfig
loggingConfig} -> Maybe LoggingConfig
loggingConfig) (\s :: DescribeTypeResponse
s@DescribeTypeResponse' {} Maybe LoggingConfig
a -> DescribeTypeResponse
s {$sel:loggingConfig:DescribeTypeResponse' :: Maybe LoggingConfig
loggingConfig = Maybe LoggingConfig
a} :: DescribeTypeResponse)

-- | For public extensions that have been activated for this account and
-- region, the Amazon Resource Name (ARN) of the public extension.
describeTypeResponse_originalTypeArn :: Lens.Lens' DescribeTypeResponse (Prelude.Maybe Prelude.Text)
describeTypeResponse_originalTypeArn :: Lens' DescribeTypeResponse (Maybe Text)
describeTypeResponse_originalTypeArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeTypeResponse' {Maybe Text
originalTypeArn :: Maybe Text
$sel:originalTypeArn:DescribeTypeResponse' :: DescribeTypeResponse -> Maybe Text
originalTypeArn} -> Maybe Text
originalTypeArn) (\s :: DescribeTypeResponse
s@DescribeTypeResponse' {} Maybe Text
a -> DescribeTypeResponse
s {$sel:originalTypeArn:DescribeTypeResponse' :: Maybe Text
originalTypeArn = Maybe Text
a} :: DescribeTypeResponse)

-- | For public extensions that have been activated for this account and
-- region, the type name of the public extension.
--
-- If you specified a @TypeNameAlias@ when enabling the extension in this
-- account and region, CloudFormation treats that alias as the extension\'s
-- type name within the account and region, not the type name of the public
-- extension. For more information, see
-- <https://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/registry-public.html#registry-public-enable-alias Specifying aliases to refer to extensions>
-- in the /CloudFormation User Guide/.
describeTypeResponse_originalTypeName :: Lens.Lens' DescribeTypeResponse (Prelude.Maybe Prelude.Text)
describeTypeResponse_originalTypeName :: Lens' DescribeTypeResponse (Maybe Text)
describeTypeResponse_originalTypeName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeTypeResponse' {Maybe Text
originalTypeName :: Maybe Text
$sel:originalTypeName:DescribeTypeResponse' :: DescribeTypeResponse -> Maybe Text
originalTypeName} -> Maybe Text
originalTypeName) (\s :: DescribeTypeResponse
s@DescribeTypeResponse' {} Maybe Text
a -> DescribeTypeResponse
s {$sel:originalTypeName:DescribeTypeResponse' :: Maybe Text
originalTypeName = Maybe Text
a} :: DescribeTypeResponse)

-- | For resource type extensions, the provisioning behavior of the resource
-- type. CloudFormation determines the provisioning type during
-- registration, based on the types of handlers in the schema handler
-- package submitted.
--
-- Valid values include:
--
-- -   @FULLY_MUTABLE@: The resource type includes an update handler to
--     process updates to the type during stack update operations.
--
-- -   @IMMUTABLE@: The resource type doesn\'t include an update handler,
--     so the type can\'t be updated and must instead be replaced during
--     stack update operations.
--
-- -   @NON_PROVISIONABLE@: The resource type doesn\'t include all the
--     following handlers, and therefore can\'t actually be provisioned.
--
--     -   create
--
--     -   read
--
--     -   delete
describeTypeResponse_provisioningType :: Lens.Lens' DescribeTypeResponse (Prelude.Maybe ProvisioningType)
describeTypeResponse_provisioningType :: Lens' DescribeTypeResponse (Maybe ProvisioningType)
describeTypeResponse_provisioningType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeTypeResponse' {Maybe ProvisioningType
provisioningType :: Maybe ProvisioningType
$sel:provisioningType:DescribeTypeResponse' :: DescribeTypeResponse -> Maybe ProvisioningType
provisioningType} -> Maybe ProvisioningType
provisioningType) (\s :: DescribeTypeResponse
s@DescribeTypeResponse' {} Maybe ProvisioningType
a -> DescribeTypeResponse
s {$sel:provisioningType:DescribeTypeResponse' :: Maybe ProvisioningType
provisioningType = Maybe ProvisioningType
a} :: DescribeTypeResponse)

-- | The version number of a public third-party extension.
--
-- This applies only if you specify a public extension you have activated
-- in your account, or specify a public extension without specifying a
-- version. For all other extensions, CloudFormation returns @null@.
describeTypeResponse_publicVersionNumber :: Lens.Lens' DescribeTypeResponse (Prelude.Maybe Prelude.Text)
describeTypeResponse_publicVersionNumber :: Lens' DescribeTypeResponse (Maybe Text)
describeTypeResponse_publicVersionNumber = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeTypeResponse' {Maybe Text
publicVersionNumber :: Maybe Text
$sel:publicVersionNumber:DescribeTypeResponse' :: DescribeTypeResponse -> Maybe Text
publicVersionNumber} -> Maybe Text
publicVersionNumber) (\s :: DescribeTypeResponse
s@DescribeTypeResponse' {} Maybe Text
a -> DescribeTypeResponse
s {$sel:publicVersionNumber:DescribeTypeResponse' :: Maybe Text
publicVersionNumber = Maybe Text
a} :: DescribeTypeResponse)

-- | The publisher ID of the extension publisher.
--
-- This applies only to public third-party extensions. For private
-- registered extensions, and extensions provided by Amazon Web Services,
-- CloudFormation returns @null@.
describeTypeResponse_publisherId :: Lens.Lens' DescribeTypeResponse (Prelude.Maybe Prelude.Text)
describeTypeResponse_publisherId :: Lens' DescribeTypeResponse (Maybe Text)
describeTypeResponse_publisherId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeTypeResponse' {Maybe Text
publisherId :: Maybe Text
$sel:publisherId:DescribeTypeResponse' :: DescribeTypeResponse -> Maybe Text
publisherId} -> Maybe Text
publisherId) (\s :: DescribeTypeResponse
s@DescribeTypeResponse' {} Maybe Text
a -> DescribeTypeResponse
s {$sel:publisherId:DescribeTypeResponse' :: Maybe Text
publisherId = Maybe Text
a} :: DescribeTypeResponse)

-- | For extensions that are modules, the public third-party extensions that
-- must be activated in your account in order for the module itself to be
-- activated.
describeTypeResponse_requiredActivatedTypes :: Lens.Lens' DescribeTypeResponse (Prelude.Maybe [RequiredActivatedType])
describeTypeResponse_requiredActivatedTypes :: Lens' DescribeTypeResponse (Maybe [RequiredActivatedType])
describeTypeResponse_requiredActivatedTypes = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeTypeResponse' {Maybe [RequiredActivatedType]
requiredActivatedTypes :: Maybe [RequiredActivatedType]
$sel:requiredActivatedTypes:DescribeTypeResponse' :: DescribeTypeResponse -> Maybe [RequiredActivatedType]
requiredActivatedTypes} -> Maybe [RequiredActivatedType]
requiredActivatedTypes) (\s :: DescribeTypeResponse
s@DescribeTypeResponse' {} Maybe [RequiredActivatedType]
a -> DescribeTypeResponse
s {$sel:requiredActivatedTypes:DescribeTypeResponse' :: Maybe [RequiredActivatedType]
requiredActivatedTypes = Maybe [RequiredActivatedType]
a} :: DescribeTypeResponse) 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 schema that defines the extension.
--
-- For more information about extension schemas, see
-- <https://docs.aws.amazon.com/cloudformation-cli/latest/userguide/resource-type-schema.html Resource Provider Schema>
-- in the /CloudFormation CLI User Guide/.
describeTypeResponse_schema :: Lens.Lens' DescribeTypeResponse (Prelude.Maybe Prelude.Text)
describeTypeResponse_schema :: Lens' DescribeTypeResponse (Maybe Text)
describeTypeResponse_schema = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeTypeResponse' {Maybe Text
schema :: Maybe Text
$sel:schema:DescribeTypeResponse' :: DescribeTypeResponse -> Maybe Text
schema} -> Maybe Text
schema) (\s :: DescribeTypeResponse
s@DescribeTypeResponse' {} Maybe Text
a -> DescribeTypeResponse
s {$sel:schema:DescribeTypeResponse' :: Maybe Text
schema = Maybe Text
a} :: DescribeTypeResponse)

-- | The URL of the source code for the extension.
describeTypeResponse_sourceUrl :: Lens.Lens' DescribeTypeResponse (Prelude.Maybe Prelude.Text)
describeTypeResponse_sourceUrl :: Lens' DescribeTypeResponse (Maybe Text)
describeTypeResponse_sourceUrl = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeTypeResponse' {Maybe Text
sourceUrl :: Maybe Text
$sel:sourceUrl:DescribeTypeResponse' :: DescribeTypeResponse -> Maybe Text
sourceUrl} -> Maybe Text
sourceUrl) (\s :: DescribeTypeResponse
s@DescribeTypeResponse' {} Maybe Text
a -> DescribeTypeResponse
s {$sel:sourceUrl:DescribeTypeResponse' :: Maybe Text
sourceUrl = Maybe Text
a} :: DescribeTypeResponse)

-- | When the specified private extension version was registered or activated
-- in your account.
describeTypeResponse_timeCreated :: Lens.Lens' DescribeTypeResponse (Prelude.Maybe Prelude.UTCTime)
describeTypeResponse_timeCreated :: Lens' DescribeTypeResponse (Maybe UTCTime)
describeTypeResponse_timeCreated = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeTypeResponse' {Maybe ISO8601
timeCreated :: Maybe ISO8601
$sel:timeCreated:DescribeTypeResponse' :: DescribeTypeResponse -> Maybe ISO8601
timeCreated} -> Maybe ISO8601
timeCreated) (\s :: DescribeTypeResponse
s@DescribeTypeResponse' {} Maybe ISO8601
a -> DescribeTypeResponse
s {$sel:timeCreated:DescribeTypeResponse' :: Maybe ISO8601
timeCreated = Maybe ISO8601
a} :: DescribeTypeResponse) 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 (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | The kind of extension.
describeTypeResponse_type :: Lens.Lens' DescribeTypeResponse (Prelude.Maybe RegistryType)
describeTypeResponse_type :: Lens' DescribeTypeResponse (Maybe RegistryType)
describeTypeResponse_type = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeTypeResponse' {Maybe RegistryType
type' :: Maybe RegistryType
$sel:type':DescribeTypeResponse' :: DescribeTypeResponse -> Maybe RegistryType
type'} -> Maybe RegistryType
type') (\s :: DescribeTypeResponse
s@DescribeTypeResponse' {} Maybe RegistryType
a -> DescribeTypeResponse
s {$sel:type':DescribeTypeResponse' :: Maybe RegistryType
type' = Maybe RegistryType
a} :: DescribeTypeResponse)

-- | The name of the extension.
--
-- If the extension is a public third-party type you have activated with a
-- type name alias, CloudFormation returns the type name alias. For more
-- information, see
-- <https://docs.aws.amazon.com/AWSCloudFormation/latest/APIReference/API_ActivateType.html ActivateType>.
describeTypeResponse_typeName :: Lens.Lens' DescribeTypeResponse (Prelude.Maybe Prelude.Text)
describeTypeResponse_typeName :: Lens' DescribeTypeResponse (Maybe Text)
describeTypeResponse_typeName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeTypeResponse' {Maybe Text
typeName :: Maybe Text
$sel:typeName:DescribeTypeResponse' :: DescribeTypeResponse -> Maybe Text
typeName} -> Maybe Text
typeName) (\s :: DescribeTypeResponse
s@DescribeTypeResponse' {} Maybe Text
a -> DescribeTypeResponse
s {$sel:typeName:DescribeTypeResponse' :: Maybe Text
typeName = Maybe Text
a} :: DescribeTypeResponse)

-- | The contract test status of the registered extension version. To return
-- the extension test status of a specific extension version, you must
-- specify @VersionId@.
--
-- This applies only to registered private extension versions.
-- CloudFormation doesn\'t return this information for public extensions,
-- whether they are activated in your account.
--
-- -   @PASSED@: The extension has passed all its contract tests.
--
--     An extension must have a test status of @PASSED@ before it can be
--     published. For more information, see
--     <https://docs.aws.amazon.com/cloudformation-cli/latest/userguide/resource-type-publish.html Publishing extensions to make them available for public use>
--     in the /CloudFormation Command Line Interface User Guide/.
--
-- -   @FAILED@: The extension has failed one or more contract tests.
--
-- -   @IN_PROGRESS@: Contract tests are currently being performed on the
--     extension.
--
-- -   @NOT_TESTED@: Contract tests haven\'t been performed on the
--     extension.
describeTypeResponse_typeTestsStatus :: Lens.Lens' DescribeTypeResponse (Prelude.Maybe TypeTestsStatus)
describeTypeResponse_typeTestsStatus :: Lens' DescribeTypeResponse (Maybe TypeTestsStatus)
describeTypeResponse_typeTestsStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeTypeResponse' {Maybe TypeTestsStatus
typeTestsStatus :: Maybe TypeTestsStatus
$sel:typeTestsStatus:DescribeTypeResponse' :: DescribeTypeResponse -> Maybe TypeTestsStatus
typeTestsStatus} -> Maybe TypeTestsStatus
typeTestsStatus) (\s :: DescribeTypeResponse
s@DescribeTypeResponse' {} Maybe TypeTestsStatus
a -> DescribeTypeResponse
s {$sel:typeTestsStatus:DescribeTypeResponse' :: Maybe TypeTestsStatus
typeTestsStatus = Maybe TypeTestsStatus
a} :: DescribeTypeResponse)

-- | The description of the test status. To return the extension test status
-- of a specific extension version, you must specify @VersionId@.
--
-- This applies only to registered private extension versions.
-- CloudFormation doesn\'t return this information for public extensions,
-- whether they are activated in your account.
describeTypeResponse_typeTestsStatusDescription :: Lens.Lens' DescribeTypeResponse (Prelude.Maybe Prelude.Text)
describeTypeResponse_typeTestsStatusDescription :: Lens' DescribeTypeResponse (Maybe Text)
describeTypeResponse_typeTestsStatusDescription = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeTypeResponse' {Maybe Text
typeTestsStatusDescription :: Maybe Text
$sel:typeTestsStatusDescription:DescribeTypeResponse' :: DescribeTypeResponse -> Maybe Text
typeTestsStatusDescription} -> Maybe Text
typeTestsStatusDescription) (\s :: DescribeTypeResponse
s@DescribeTypeResponse' {} Maybe Text
a -> DescribeTypeResponse
s {$sel:typeTestsStatusDescription:DescribeTypeResponse' :: Maybe Text
typeTestsStatusDescription = Maybe Text
a} :: DescribeTypeResponse)

-- | The scope at which the extension is visible and usable in CloudFormation
-- operations.
--
-- Valid values include:
--
-- -   @PRIVATE@: The extension is only visible and usable within the
--     account in which it is registered. CloudFormation marks any
--     extensions you register as @PRIVATE@.
--
-- -   @PUBLIC@: The extension is publicly visible and usable within any
--     Amazon Web Services account.
describeTypeResponse_visibility :: Lens.Lens' DescribeTypeResponse (Prelude.Maybe Visibility)
describeTypeResponse_visibility :: Lens' DescribeTypeResponse (Maybe Visibility)
describeTypeResponse_visibility = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeTypeResponse' {Maybe Visibility
visibility :: Maybe Visibility
$sel:visibility:DescribeTypeResponse' :: DescribeTypeResponse -> Maybe Visibility
visibility} -> Maybe Visibility
visibility) (\s :: DescribeTypeResponse
s@DescribeTypeResponse' {} Maybe Visibility
a -> DescribeTypeResponse
s {$sel:visibility:DescribeTypeResponse' :: Maybe Visibility
visibility = Maybe Visibility
a} :: DescribeTypeResponse)

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

instance Prelude.NFData DescribeTypeResponse where
  rnf :: DescribeTypeResponse -> ()
rnf DescribeTypeResponse' {Int
Maybe Bool
Maybe [RequiredActivatedType]
Maybe Text
Maybe ISO8601
Maybe DeprecatedStatus
Maybe LoggingConfig
Maybe ProvisioningType
Maybe RegistryType
Maybe TypeTestsStatus
Maybe Visibility
httpStatus :: Int
visibility :: Maybe Visibility
typeTestsStatusDescription :: Maybe Text
typeTestsStatus :: Maybe TypeTestsStatus
typeName :: Maybe Text
type' :: Maybe RegistryType
timeCreated :: Maybe ISO8601
sourceUrl :: Maybe Text
schema :: Maybe Text
requiredActivatedTypes :: Maybe [RequiredActivatedType]
publisherId :: Maybe Text
publicVersionNumber :: Maybe Text
provisioningType :: Maybe ProvisioningType
originalTypeName :: Maybe Text
originalTypeArn :: Maybe Text
loggingConfig :: Maybe LoggingConfig
latestPublicVersion :: Maybe Text
lastUpdated :: Maybe ISO8601
isDefaultVersion :: Maybe Bool
isActivated :: Maybe Bool
executionRoleArn :: Maybe Text
documentationUrl :: Maybe Text
description :: Maybe Text
deprecatedStatus :: Maybe DeprecatedStatus
defaultVersionId :: Maybe Text
configurationSchema :: Maybe Text
autoUpdate :: Maybe Bool
arn :: Maybe Text
$sel:httpStatus:DescribeTypeResponse' :: DescribeTypeResponse -> Int
$sel:visibility:DescribeTypeResponse' :: DescribeTypeResponse -> Maybe Visibility
$sel:typeTestsStatusDescription:DescribeTypeResponse' :: DescribeTypeResponse -> Maybe Text
$sel:typeTestsStatus:DescribeTypeResponse' :: DescribeTypeResponse -> Maybe TypeTestsStatus
$sel:typeName:DescribeTypeResponse' :: DescribeTypeResponse -> Maybe Text
$sel:type':DescribeTypeResponse' :: DescribeTypeResponse -> Maybe RegistryType
$sel:timeCreated:DescribeTypeResponse' :: DescribeTypeResponse -> Maybe ISO8601
$sel:sourceUrl:DescribeTypeResponse' :: DescribeTypeResponse -> Maybe Text
$sel:schema:DescribeTypeResponse' :: DescribeTypeResponse -> Maybe Text
$sel:requiredActivatedTypes:DescribeTypeResponse' :: DescribeTypeResponse -> Maybe [RequiredActivatedType]
$sel:publisherId:DescribeTypeResponse' :: DescribeTypeResponse -> Maybe Text
$sel:publicVersionNumber:DescribeTypeResponse' :: DescribeTypeResponse -> Maybe Text
$sel:provisioningType:DescribeTypeResponse' :: DescribeTypeResponse -> Maybe ProvisioningType
$sel:originalTypeName:DescribeTypeResponse' :: DescribeTypeResponse -> Maybe Text
$sel:originalTypeArn:DescribeTypeResponse' :: DescribeTypeResponse -> Maybe Text
$sel:loggingConfig:DescribeTypeResponse' :: DescribeTypeResponse -> Maybe LoggingConfig
$sel:latestPublicVersion:DescribeTypeResponse' :: DescribeTypeResponse -> Maybe Text
$sel:lastUpdated:DescribeTypeResponse' :: DescribeTypeResponse -> Maybe ISO8601
$sel:isDefaultVersion:DescribeTypeResponse' :: DescribeTypeResponse -> Maybe Bool
$sel:isActivated:DescribeTypeResponse' :: DescribeTypeResponse -> Maybe Bool
$sel:executionRoleArn:DescribeTypeResponse' :: DescribeTypeResponse -> Maybe Text
$sel:documentationUrl:DescribeTypeResponse' :: DescribeTypeResponse -> Maybe Text
$sel:description:DescribeTypeResponse' :: DescribeTypeResponse -> Maybe Text
$sel:deprecatedStatus:DescribeTypeResponse' :: DescribeTypeResponse -> Maybe DeprecatedStatus
$sel:defaultVersionId:DescribeTypeResponse' :: DescribeTypeResponse -> Maybe Text
$sel:configurationSchema:DescribeTypeResponse' :: DescribeTypeResponse -> Maybe Text
$sel:autoUpdate:DescribeTypeResponse' :: DescribeTypeResponse -> Maybe Bool
$sel:arn:DescribeTypeResponse' :: DescribeTypeResponse -> 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 Bool
autoUpdate
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
configurationSchema
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
defaultVersionId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe DeprecatedStatus
deprecatedStatus
      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 Text
documentationUrl
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
executionRoleArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
isActivated
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
isDefaultVersion
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ISO8601
lastUpdated
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
latestPublicVersion
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe LoggingConfig
loggingConfig
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
originalTypeArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
originalTypeName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ProvisioningType
provisioningType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
publicVersionNumber
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
publisherId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe [RequiredActivatedType]
requiredActivatedTypes
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
schema
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
sourceUrl
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ISO8601
timeCreated
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe RegistryType
type'
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
typeName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe TypeTestsStatus
typeTestsStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe Text
typeTestsStatusDescription
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe Visibility
visibility
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Int
httpStatus