{-# 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.ECS.DescribeTaskDefinition
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Describes a task definition. You can specify a @family@ and @revision@
-- to find information about a specific task definition, or you can simply
-- specify the family to find the latest @ACTIVE@ revision in that family.
--
-- You can only describe @INACTIVE@ task definitions while an active task
-- or service references them.
module Amazonka.ECS.DescribeTaskDefinition
  ( -- * Creating a Request
    DescribeTaskDefinition (..),
    newDescribeTaskDefinition,

    -- * Request Lenses
    describeTaskDefinition_include,
    describeTaskDefinition_taskDefinition,

    -- * Destructuring the Response
    DescribeTaskDefinitionResponse (..),
    newDescribeTaskDefinitionResponse,

    -- * Response Lenses
    describeTaskDefinitionResponse_tags,
    describeTaskDefinitionResponse_taskDefinition,
    describeTaskDefinitionResponse_httpStatus,
  )
where

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

-- | /See:/ 'newDescribeTaskDefinition' smart constructor.
data DescribeTaskDefinition = DescribeTaskDefinition'
  { -- | Determines whether to see the resource tags for the task definition. If
    -- @TAGS@ is specified, the tags are included in the response. If this
    -- field is omitted, tags aren\'t included in the response.
    DescribeTaskDefinition -> Maybe [TaskDefinitionField]
include :: Prelude.Maybe [TaskDefinitionField],
    -- | The @family@ for the latest @ACTIVE@ revision, @family@ and @revision@
    -- (@family:revision@) for a specific revision in the family, or full
    -- Amazon Resource Name (ARN) of the task definition to describe.
    DescribeTaskDefinition -> Text
taskDefinition :: Prelude.Text
  }
  deriving (DescribeTaskDefinition -> DescribeTaskDefinition -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeTaskDefinition -> DescribeTaskDefinition -> Bool
$c/= :: DescribeTaskDefinition -> DescribeTaskDefinition -> Bool
== :: DescribeTaskDefinition -> DescribeTaskDefinition -> Bool
$c== :: DescribeTaskDefinition -> DescribeTaskDefinition -> Bool
Prelude.Eq, ReadPrec [DescribeTaskDefinition]
ReadPrec DescribeTaskDefinition
Int -> ReadS DescribeTaskDefinition
ReadS [DescribeTaskDefinition]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeTaskDefinition]
$creadListPrec :: ReadPrec [DescribeTaskDefinition]
readPrec :: ReadPrec DescribeTaskDefinition
$creadPrec :: ReadPrec DescribeTaskDefinition
readList :: ReadS [DescribeTaskDefinition]
$creadList :: ReadS [DescribeTaskDefinition]
readsPrec :: Int -> ReadS DescribeTaskDefinition
$creadsPrec :: Int -> ReadS DescribeTaskDefinition
Prelude.Read, Int -> DescribeTaskDefinition -> ShowS
[DescribeTaskDefinition] -> ShowS
DescribeTaskDefinition -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeTaskDefinition] -> ShowS
$cshowList :: [DescribeTaskDefinition] -> ShowS
show :: DescribeTaskDefinition -> String
$cshow :: DescribeTaskDefinition -> String
showsPrec :: Int -> DescribeTaskDefinition -> ShowS
$cshowsPrec :: Int -> DescribeTaskDefinition -> ShowS
Prelude.Show, forall x. Rep DescribeTaskDefinition x -> DescribeTaskDefinition
forall x. DescribeTaskDefinition -> Rep DescribeTaskDefinition x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DescribeTaskDefinition x -> DescribeTaskDefinition
$cfrom :: forall x. DescribeTaskDefinition -> Rep DescribeTaskDefinition x
Prelude.Generic)

-- |
-- Create a value of 'DescribeTaskDefinition' 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:
--
-- 'include', 'describeTaskDefinition_include' - Determines whether to see the resource tags for the task definition. If
-- @TAGS@ is specified, the tags are included in the response. If this
-- field is omitted, tags aren\'t included in the response.
--
-- 'taskDefinition', 'describeTaskDefinition_taskDefinition' - The @family@ for the latest @ACTIVE@ revision, @family@ and @revision@
-- (@family:revision@) for a specific revision in the family, or full
-- Amazon Resource Name (ARN) of the task definition to describe.
newDescribeTaskDefinition ::
  -- | 'taskDefinition'
  Prelude.Text ->
  DescribeTaskDefinition
newDescribeTaskDefinition :: Text -> DescribeTaskDefinition
newDescribeTaskDefinition Text
pTaskDefinition_ =
  DescribeTaskDefinition'
    { $sel:include:DescribeTaskDefinition' :: Maybe [TaskDefinitionField]
include = forall a. Maybe a
Prelude.Nothing,
      $sel:taskDefinition:DescribeTaskDefinition' :: Text
taskDefinition = Text
pTaskDefinition_
    }

-- | Determines whether to see the resource tags for the task definition. If
-- @TAGS@ is specified, the tags are included in the response. If this
-- field is omitted, tags aren\'t included in the response.
describeTaskDefinition_include :: Lens.Lens' DescribeTaskDefinition (Prelude.Maybe [TaskDefinitionField])
describeTaskDefinition_include :: Lens' DescribeTaskDefinition (Maybe [TaskDefinitionField])
describeTaskDefinition_include = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeTaskDefinition' {Maybe [TaskDefinitionField]
include :: Maybe [TaskDefinitionField]
$sel:include:DescribeTaskDefinition' :: DescribeTaskDefinition -> Maybe [TaskDefinitionField]
include} -> Maybe [TaskDefinitionField]
include) (\s :: DescribeTaskDefinition
s@DescribeTaskDefinition' {} Maybe [TaskDefinitionField]
a -> DescribeTaskDefinition
s {$sel:include:DescribeTaskDefinition' :: Maybe [TaskDefinitionField]
include = Maybe [TaskDefinitionField]
a} :: DescribeTaskDefinition) 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 @family@ for the latest @ACTIVE@ revision, @family@ and @revision@
-- (@family:revision@) for a specific revision in the family, or full
-- Amazon Resource Name (ARN) of the task definition to describe.
describeTaskDefinition_taskDefinition :: Lens.Lens' DescribeTaskDefinition Prelude.Text
describeTaskDefinition_taskDefinition :: Lens' DescribeTaskDefinition Text
describeTaskDefinition_taskDefinition = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeTaskDefinition' {Text
taskDefinition :: Text
$sel:taskDefinition:DescribeTaskDefinition' :: DescribeTaskDefinition -> Text
taskDefinition} -> Text
taskDefinition) (\s :: DescribeTaskDefinition
s@DescribeTaskDefinition' {} Text
a -> DescribeTaskDefinition
s {$sel:taskDefinition:DescribeTaskDefinition' :: Text
taskDefinition = Text
a} :: DescribeTaskDefinition)

instance Core.AWSRequest DescribeTaskDefinition where
  type
    AWSResponse DescribeTaskDefinition =
      DescribeTaskDefinitionResponse
  request :: (Service -> Service)
-> DescribeTaskDefinition -> Request DescribeTaskDefinition
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.postJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy DescribeTaskDefinition
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DescribeTaskDefinition)))
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 [Tag]
-> Maybe TaskDefinition -> Int -> DescribeTaskDefinitionResponse
DescribeTaskDefinitionResponse'
            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
"tags" forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty)
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"taskDefinition")
            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 DescribeTaskDefinition where
  hashWithSalt :: Int -> DescribeTaskDefinition -> Int
hashWithSalt Int
_salt DescribeTaskDefinition' {Maybe [TaskDefinitionField]
Text
taskDefinition :: Text
include :: Maybe [TaskDefinitionField]
$sel:taskDefinition:DescribeTaskDefinition' :: DescribeTaskDefinition -> Text
$sel:include:DescribeTaskDefinition' :: DescribeTaskDefinition -> Maybe [TaskDefinitionField]
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [TaskDefinitionField]
include
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
taskDefinition

instance Prelude.NFData DescribeTaskDefinition where
  rnf :: DescribeTaskDefinition -> ()
rnf DescribeTaskDefinition' {Maybe [TaskDefinitionField]
Text
taskDefinition :: Text
include :: Maybe [TaskDefinitionField]
$sel:taskDefinition:DescribeTaskDefinition' :: DescribeTaskDefinition -> Text
$sel:include:DescribeTaskDefinition' :: DescribeTaskDefinition -> Maybe [TaskDefinitionField]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [TaskDefinitionField]
include
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
taskDefinition

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

instance Data.ToJSON DescribeTaskDefinition where
  toJSON :: DescribeTaskDefinition -> Value
toJSON DescribeTaskDefinition' {Maybe [TaskDefinitionField]
Text
taskDefinition :: Text
include :: Maybe [TaskDefinitionField]
$sel:taskDefinition:DescribeTaskDefinition' :: DescribeTaskDefinition -> Text
$sel:include:DescribeTaskDefinition' :: DescribeTaskDefinition -> Maybe [TaskDefinitionField]
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"include" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [TaskDefinitionField]
include,
            forall a. a -> Maybe a
Prelude.Just
              (Key
"taskDefinition" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
taskDefinition)
          ]
      )

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

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

-- | /See:/ 'newDescribeTaskDefinitionResponse' smart constructor.
data DescribeTaskDefinitionResponse = DescribeTaskDefinitionResponse'
  { -- | The metadata that\'s applied to the task definition to help you
    -- categorize and organize them. Each tag consists of a key and an optional
    -- value. You define both.
    --
    -- The following basic restrictions apply to tags:
    --
    -- -   Maximum number of tags per resource - 50
    --
    -- -   For each resource, each tag key must be unique, and each tag key can
    --     have only one value.
    --
    -- -   Maximum key length - 128 Unicode characters in UTF-8
    --
    -- -   Maximum value length - 256 Unicode characters in UTF-8
    --
    -- -   If your tagging schema is used across multiple services and
    --     resources, remember that other services may have restrictions on
    --     allowed characters. Generally allowed characters are: letters,
    --     numbers, and spaces representable in UTF-8, and the following
    --     characters: + - = . _ : \/ \@.
    --
    -- -   Tag keys and values are case-sensitive.
    --
    -- -   Do not use @aws:@, @AWS:@, or any upper or lowercase combination of
    --     such as a prefix for either keys or values as it is reserved for
    --     Amazon Web Services use. You cannot edit or delete tag keys or
    --     values with this prefix. Tags with this prefix do not count against
    --     your tags per resource limit.
    DescribeTaskDefinitionResponse -> Maybe [Tag]
tags :: Prelude.Maybe [Tag],
    -- | The full task definition description.
    DescribeTaskDefinitionResponse -> Maybe TaskDefinition
taskDefinition :: Prelude.Maybe TaskDefinition,
    -- | The response's http status code.
    DescribeTaskDefinitionResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DescribeTaskDefinitionResponse
-> DescribeTaskDefinitionResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeTaskDefinitionResponse
-> DescribeTaskDefinitionResponse -> Bool
$c/= :: DescribeTaskDefinitionResponse
-> DescribeTaskDefinitionResponse -> Bool
== :: DescribeTaskDefinitionResponse
-> DescribeTaskDefinitionResponse -> Bool
$c== :: DescribeTaskDefinitionResponse
-> DescribeTaskDefinitionResponse -> Bool
Prelude.Eq, ReadPrec [DescribeTaskDefinitionResponse]
ReadPrec DescribeTaskDefinitionResponse
Int -> ReadS DescribeTaskDefinitionResponse
ReadS [DescribeTaskDefinitionResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeTaskDefinitionResponse]
$creadListPrec :: ReadPrec [DescribeTaskDefinitionResponse]
readPrec :: ReadPrec DescribeTaskDefinitionResponse
$creadPrec :: ReadPrec DescribeTaskDefinitionResponse
readList :: ReadS [DescribeTaskDefinitionResponse]
$creadList :: ReadS [DescribeTaskDefinitionResponse]
readsPrec :: Int -> ReadS DescribeTaskDefinitionResponse
$creadsPrec :: Int -> ReadS DescribeTaskDefinitionResponse
Prelude.Read, Int -> DescribeTaskDefinitionResponse -> ShowS
[DescribeTaskDefinitionResponse] -> ShowS
DescribeTaskDefinitionResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeTaskDefinitionResponse] -> ShowS
$cshowList :: [DescribeTaskDefinitionResponse] -> ShowS
show :: DescribeTaskDefinitionResponse -> String
$cshow :: DescribeTaskDefinitionResponse -> String
showsPrec :: Int -> DescribeTaskDefinitionResponse -> ShowS
$cshowsPrec :: Int -> DescribeTaskDefinitionResponse -> ShowS
Prelude.Show, forall x.
Rep DescribeTaskDefinitionResponse x
-> DescribeTaskDefinitionResponse
forall x.
DescribeTaskDefinitionResponse
-> Rep DescribeTaskDefinitionResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeTaskDefinitionResponse x
-> DescribeTaskDefinitionResponse
$cfrom :: forall x.
DescribeTaskDefinitionResponse
-> Rep DescribeTaskDefinitionResponse x
Prelude.Generic)

-- |
-- Create a value of 'DescribeTaskDefinitionResponse' 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:
--
-- 'tags', 'describeTaskDefinitionResponse_tags' - The metadata that\'s applied to the task definition to help you
-- categorize and organize them. Each tag consists of a key and an optional
-- value. You define both.
--
-- The following basic restrictions apply to tags:
--
-- -   Maximum number of tags per resource - 50
--
-- -   For each resource, each tag key must be unique, and each tag key can
--     have only one value.
--
-- -   Maximum key length - 128 Unicode characters in UTF-8
--
-- -   Maximum value length - 256 Unicode characters in UTF-8
--
-- -   If your tagging schema is used across multiple services and
--     resources, remember that other services may have restrictions on
--     allowed characters. Generally allowed characters are: letters,
--     numbers, and spaces representable in UTF-8, and the following
--     characters: + - = . _ : \/ \@.
--
-- -   Tag keys and values are case-sensitive.
--
-- -   Do not use @aws:@, @AWS:@, or any upper or lowercase combination of
--     such as a prefix for either keys or values as it is reserved for
--     Amazon Web Services use. You cannot edit or delete tag keys or
--     values with this prefix. Tags with this prefix do not count against
--     your tags per resource limit.
--
-- 'taskDefinition', 'describeTaskDefinitionResponse_taskDefinition' - The full task definition description.
--
-- 'httpStatus', 'describeTaskDefinitionResponse_httpStatus' - The response's http status code.
newDescribeTaskDefinitionResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DescribeTaskDefinitionResponse
newDescribeTaskDefinitionResponse :: Int -> DescribeTaskDefinitionResponse
newDescribeTaskDefinitionResponse Int
pHttpStatus_ =
  DescribeTaskDefinitionResponse'
    { $sel:tags:DescribeTaskDefinitionResponse' :: Maybe [Tag]
tags =
        forall a. Maybe a
Prelude.Nothing,
      $sel:taskDefinition:DescribeTaskDefinitionResponse' :: Maybe TaskDefinition
taskDefinition = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DescribeTaskDefinitionResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The metadata that\'s applied to the task definition to help you
-- categorize and organize them. Each tag consists of a key and an optional
-- value. You define both.
--
-- The following basic restrictions apply to tags:
--
-- -   Maximum number of tags per resource - 50
--
-- -   For each resource, each tag key must be unique, and each tag key can
--     have only one value.
--
-- -   Maximum key length - 128 Unicode characters in UTF-8
--
-- -   Maximum value length - 256 Unicode characters in UTF-8
--
-- -   If your tagging schema is used across multiple services and
--     resources, remember that other services may have restrictions on
--     allowed characters. Generally allowed characters are: letters,
--     numbers, and spaces representable in UTF-8, and the following
--     characters: + - = . _ : \/ \@.
--
-- -   Tag keys and values are case-sensitive.
--
-- -   Do not use @aws:@, @AWS:@, or any upper or lowercase combination of
--     such as a prefix for either keys or values as it is reserved for
--     Amazon Web Services use. You cannot edit or delete tag keys or
--     values with this prefix. Tags with this prefix do not count against
--     your tags per resource limit.
describeTaskDefinitionResponse_tags :: Lens.Lens' DescribeTaskDefinitionResponse (Prelude.Maybe [Tag])
describeTaskDefinitionResponse_tags :: Lens' DescribeTaskDefinitionResponse (Maybe [Tag])
describeTaskDefinitionResponse_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeTaskDefinitionResponse' {Maybe [Tag]
tags :: Maybe [Tag]
$sel:tags:DescribeTaskDefinitionResponse' :: DescribeTaskDefinitionResponse -> Maybe [Tag]
tags} -> Maybe [Tag]
tags) (\s :: DescribeTaskDefinitionResponse
s@DescribeTaskDefinitionResponse' {} Maybe [Tag]
a -> DescribeTaskDefinitionResponse
s {$sel:tags:DescribeTaskDefinitionResponse' :: Maybe [Tag]
tags = Maybe [Tag]
a} :: DescribeTaskDefinitionResponse) 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 full task definition description.
describeTaskDefinitionResponse_taskDefinition :: Lens.Lens' DescribeTaskDefinitionResponse (Prelude.Maybe TaskDefinition)
describeTaskDefinitionResponse_taskDefinition :: Lens' DescribeTaskDefinitionResponse (Maybe TaskDefinition)
describeTaskDefinitionResponse_taskDefinition = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeTaskDefinitionResponse' {Maybe TaskDefinition
taskDefinition :: Maybe TaskDefinition
$sel:taskDefinition:DescribeTaskDefinitionResponse' :: DescribeTaskDefinitionResponse -> Maybe TaskDefinition
taskDefinition} -> Maybe TaskDefinition
taskDefinition) (\s :: DescribeTaskDefinitionResponse
s@DescribeTaskDefinitionResponse' {} Maybe TaskDefinition
a -> DescribeTaskDefinitionResponse
s {$sel:taskDefinition:DescribeTaskDefinitionResponse' :: Maybe TaskDefinition
taskDefinition = Maybe TaskDefinition
a} :: DescribeTaskDefinitionResponse)

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

instance
  Prelude.NFData
    DescribeTaskDefinitionResponse
  where
  rnf :: DescribeTaskDefinitionResponse -> ()
rnf DescribeTaskDefinitionResponse' {Int
Maybe [Tag]
Maybe TaskDefinition
httpStatus :: Int
taskDefinition :: Maybe TaskDefinition
tags :: Maybe [Tag]
$sel:httpStatus:DescribeTaskDefinitionResponse' :: DescribeTaskDefinitionResponse -> Int
$sel:taskDefinition:DescribeTaskDefinitionResponse' :: DescribeTaskDefinitionResponse -> Maybe TaskDefinition
$sel:tags:DescribeTaskDefinitionResponse' :: DescribeTaskDefinitionResponse -> Maybe [Tag]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [Tag]
tags
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe TaskDefinition
taskDefinition
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus