{-# 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.DescribeStackInstance
-- 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 the stack instance that\'s associated with the specified stack
-- set, Amazon Web Services account, and Region.
--
-- For a list of stack instances that are associated with a specific stack
-- set, use ListStackInstances.
module Amazonka.CloudFormation.DescribeStackInstance
  ( -- * Creating a Request
    DescribeStackInstance (..),
    newDescribeStackInstance,

    -- * Request Lenses
    describeStackInstance_callAs,
    describeStackInstance_stackSetName,
    describeStackInstance_stackInstanceAccount,
    describeStackInstance_stackInstanceRegion,

    -- * Destructuring the Response
    DescribeStackInstanceResponse (..),
    newDescribeStackInstanceResponse,

    -- * Response Lenses
    describeStackInstanceResponse_stackInstance,
    describeStackInstanceResponse_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:/ 'newDescribeStackInstance' smart constructor.
data DescribeStackInstance = DescribeStackInstance'
  { -- | [Service-managed permissions] Specifies whether you are acting as an
    -- account administrator in the organization\'s management account or as a
    -- delegated administrator in a member account.
    --
    -- By default, @SELF@ is specified. Use @SELF@ for stack sets with
    -- self-managed permissions.
    --
    -- -   If you are signed in to the management account, specify @SELF@.
    --
    -- -   If you are signed in to a delegated administrator account, specify
    --     @DELEGATED_ADMIN@.
    --
    --     Your Amazon Web Services account must be registered as a delegated
    --     administrator in the management account. For more information, see
    --     <https://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/stacksets-orgs-delegated-admin.html Register a delegated administrator>
    --     in the /CloudFormation User Guide/.
    DescribeStackInstance -> Maybe CallAs
callAs :: Prelude.Maybe CallAs,
    -- | The name or the unique stack ID of the stack set that you want to get
    -- stack instance information for.
    DescribeStackInstance -> Text
stackSetName :: Prelude.Text,
    -- | The ID of an Amazon Web Services account that\'s associated with this
    -- stack instance.
    DescribeStackInstance -> Text
stackInstanceAccount :: Prelude.Text,
    -- | The name of a Region that\'s associated with this stack instance.
    DescribeStackInstance -> Text
stackInstanceRegion :: Prelude.Text
  }
  deriving (DescribeStackInstance -> DescribeStackInstance -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeStackInstance -> DescribeStackInstance -> Bool
$c/= :: DescribeStackInstance -> DescribeStackInstance -> Bool
== :: DescribeStackInstance -> DescribeStackInstance -> Bool
$c== :: DescribeStackInstance -> DescribeStackInstance -> Bool
Prelude.Eq, ReadPrec [DescribeStackInstance]
ReadPrec DescribeStackInstance
Int -> ReadS DescribeStackInstance
ReadS [DescribeStackInstance]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeStackInstance]
$creadListPrec :: ReadPrec [DescribeStackInstance]
readPrec :: ReadPrec DescribeStackInstance
$creadPrec :: ReadPrec DescribeStackInstance
readList :: ReadS [DescribeStackInstance]
$creadList :: ReadS [DescribeStackInstance]
readsPrec :: Int -> ReadS DescribeStackInstance
$creadsPrec :: Int -> ReadS DescribeStackInstance
Prelude.Read, Int -> DescribeStackInstance -> ShowS
[DescribeStackInstance] -> ShowS
DescribeStackInstance -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeStackInstance] -> ShowS
$cshowList :: [DescribeStackInstance] -> ShowS
show :: DescribeStackInstance -> String
$cshow :: DescribeStackInstance -> String
showsPrec :: Int -> DescribeStackInstance -> ShowS
$cshowsPrec :: Int -> DescribeStackInstance -> ShowS
Prelude.Show, forall x. Rep DescribeStackInstance x -> DescribeStackInstance
forall x. DescribeStackInstance -> Rep DescribeStackInstance x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DescribeStackInstance x -> DescribeStackInstance
$cfrom :: forall x. DescribeStackInstance -> Rep DescribeStackInstance x
Prelude.Generic)

-- |
-- Create a value of 'DescribeStackInstance' 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:
--
-- 'callAs', 'describeStackInstance_callAs' - [Service-managed permissions] Specifies whether you are acting as an
-- account administrator in the organization\'s management account or as a
-- delegated administrator in a member account.
--
-- By default, @SELF@ is specified. Use @SELF@ for stack sets with
-- self-managed permissions.
--
-- -   If you are signed in to the management account, specify @SELF@.
--
-- -   If you are signed in to a delegated administrator account, specify
--     @DELEGATED_ADMIN@.
--
--     Your Amazon Web Services account must be registered as a delegated
--     administrator in the management account. For more information, see
--     <https://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/stacksets-orgs-delegated-admin.html Register a delegated administrator>
--     in the /CloudFormation User Guide/.
--
-- 'stackSetName', 'describeStackInstance_stackSetName' - The name or the unique stack ID of the stack set that you want to get
-- stack instance information for.
--
-- 'stackInstanceAccount', 'describeStackInstance_stackInstanceAccount' - The ID of an Amazon Web Services account that\'s associated with this
-- stack instance.
--
-- 'stackInstanceRegion', 'describeStackInstance_stackInstanceRegion' - The name of a Region that\'s associated with this stack instance.
newDescribeStackInstance ::
  -- | 'stackSetName'
  Prelude.Text ->
  -- | 'stackInstanceAccount'
  Prelude.Text ->
  -- | 'stackInstanceRegion'
  Prelude.Text ->
  DescribeStackInstance
newDescribeStackInstance :: Text -> Text -> Text -> DescribeStackInstance
newDescribeStackInstance
  Text
pStackSetName_
  Text
pStackInstanceAccount_
  Text
pStackInstanceRegion_ =
    DescribeStackInstance'
      { $sel:callAs:DescribeStackInstance' :: Maybe CallAs
callAs = forall a. Maybe a
Prelude.Nothing,
        $sel:stackSetName:DescribeStackInstance' :: Text
stackSetName = Text
pStackSetName_,
        $sel:stackInstanceAccount:DescribeStackInstance' :: Text
stackInstanceAccount = Text
pStackInstanceAccount_,
        $sel:stackInstanceRegion:DescribeStackInstance' :: Text
stackInstanceRegion = Text
pStackInstanceRegion_
      }

-- | [Service-managed permissions] Specifies whether you are acting as an
-- account administrator in the organization\'s management account or as a
-- delegated administrator in a member account.
--
-- By default, @SELF@ is specified. Use @SELF@ for stack sets with
-- self-managed permissions.
--
-- -   If you are signed in to the management account, specify @SELF@.
--
-- -   If you are signed in to a delegated administrator account, specify
--     @DELEGATED_ADMIN@.
--
--     Your Amazon Web Services account must be registered as a delegated
--     administrator in the management account. For more information, see
--     <https://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/stacksets-orgs-delegated-admin.html Register a delegated administrator>
--     in the /CloudFormation User Guide/.
describeStackInstance_callAs :: Lens.Lens' DescribeStackInstance (Prelude.Maybe CallAs)
describeStackInstance_callAs :: Lens' DescribeStackInstance (Maybe CallAs)
describeStackInstance_callAs = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeStackInstance' {Maybe CallAs
callAs :: Maybe CallAs
$sel:callAs:DescribeStackInstance' :: DescribeStackInstance -> Maybe CallAs
callAs} -> Maybe CallAs
callAs) (\s :: DescribeStackInstance
s@DescribeStackInstance' {} Maybe CallAs
a -> DescribeStackInstance
s {$sel:callAs:DescribeStackInstance' :: Maybe CallAs
callAs = Maybe CallAs
a} :: DescribeStackInstance)

-- | The name or the unique stack ID of the stack set that you want to get
-- stack instance information for.
describeStackInstance_stackSetName :: Lens.Lens' DescribeStackInstance Prelude.Text
describeStackInstance_stackSetName :: Lens' DescribeStackInstance Text
describeStackInstance_stackSetName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeStackInstance' {Text
stackSetName :: Text
$sel:stackSetName:DescribeStackInstance' :: DescribeStackInstance -> Text
stackSetName} -> Text
stackSetName) (\s :: DescribeStackInstance
s@DescribeStackInstance' {} Text
a -> DescribeStackInstance
s {$sel:stackSetName:DescribeStackInstance' :: Text
stackSetName = Text
a} :: DescribeStackInstance)

-- | The ID of an Amazon Web Services account that\'s associated with this
-- stack instance.
describeStackInstance_stackInstanceAccount :: Lens.Lens' DescribeStackInstance Prelude.Text
describeStackInstance_stackInstanceAccount :: Lens' DescribeStackInstance Text
describeStackInstance_stackInstanceAccount = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeStackInstance' {Text
stackInstanceAccount :: Text
$sel:stackInstanceAccount:DescribeStackInstance' :: DescribeStackInstance -> Text
stackInstanceAccount} -> Text
stackInstanceAccount) (\s :: DescribeStackInstance
s@DescribeStackInstance' {} Text
a -> DescribeStackInstance
s {$sel:stackInstanceAccount:DescribeStackInstance' :: Text
stackInstanceAccount = Text
a} :: DescribeStackInstance)

-- | The name of a Region that\'s associated with this stack instance.
describeStackInstance_stackInstanceRegion :: Lens.Lens' DescribeStackInstance Prelude.Text
describeStackInstance_stackInstanceRegion :: Lens' DescribeStackInstance Text
describeStackInstance_stackInstanceRegion = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeStackInstance' {Text
stackInstanceRegion :: Text
$sel:stackInstanceRegion:DescribeStackInstance' :: DescribeStackInstance -> Text
stackInstanceRegion} -> Text
stackInstanceRegion) (\s :: DescribeStackInstance
s@DescribeStackInstance' {} Text
a -> DescribeStackInstance
s {$sel:stackInstanceRegion:DescribeStackInstance' :: Text
stackInstanceRegion = Text
a} :: DescribeStackInstance)

instance Core.AWSRequest DescribeStackInstance where
  type
    AWSResponse DescribeStackInstance =
      DescribeStackInstanceResponse
  request :: (Service -> Service)
-> DescribeStackInstance -> Request DescribeStackInstance
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 DescribeStackInstance
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DescribeStackInstance)))
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
"DescribeStackInstanceResult"
      ( \Int
s ResponseHeaders
h [Node]
x ->
          Maybe StackInstance -> Int -> DescribeStackInstanceResponse
DescribeStackInstanceResponse'
            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
"StackInstance")
            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 DescribeStackInstance where
  hashWithSalt :: Int -> DescribeStackInstance -> Int
hashWithSalt Int
_salt DescribeStackInstance' {Maybe CallAs
Text
stackInstanceRegion :: Text
stackInstanceAccount :: Text
stackSetName :: Text
callAs :: Maybe CallAs
$sel:stackInstanceRegion:DescribeStackInstance' :: DescribeStackInstance -> Text
$sel:stackInstanceAccount:DescribeStackInstance' :: DescribeStackInstance -> Text
$sel:stackSetName:DescribeStackInstance' :: DescribeStackInstance -> Text
$sel:callAs:DescribeStackInstance' :: DescribeStackInstance -> Maybe CallAs
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe CallAs
callAs
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
stackSetName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
stackInstanceAccount
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
stackInstanceRegion

instance Prelude.NFData DescribeStackInstance where
  rnf :: DescribeStackInstance -> ()
rnf DescribeStackInstance' {Maybe CallAs
Text
stackInstanceRegion :: Text
stackInstanceAccount :: Text
stackSetName :: Text
callAs :: Maybe CallAs
$sel:stackInstanceRegion:DescribeStackInstance' :: DescribeStackInstance -> Text
$sel:stackInstanceAccount:DescribeStackInstance' :: DescribeStackInstance -> Text
$sel:stackSetName:DescribeStackInstance' :: DescribeStackInstance -> Text
$sel:callAs:DescribeStackInstance' :: DescribeStackInstance -> Maybe CallAs
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe CallAs
callAs
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
stackSetName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
stackInstanceAccount
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
stackInstanceRegion

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

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

instance Data.ToQuery DescribeStackInstance where
  toQuery :: DescribeStackInstance -> QueryString
toQuery DescribeStackInstance' {Maybe CallAs
Text
stackInstanceRegion :: Text
stackInstanceAccount :: Text
stackSetName :: Text
callAs :: Maybe CallAs
$sel:stackInstanceRegion:DescribeStackInstance' :: DescribeStackInstance -> Text
$sel:stackInstanceAccount:DescribeStackInstance' :: DescribeStackInstance -> Text
$sel:stackSetName:DescribeStackInstance' :: DescribeStackInstance -> Text
$sel:callAs:DescribeStackInstance' :: DescribeStackInstance -> Maybe CallAs
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"DescribeStackInstance" :: Prelude.ByteString),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2010-05-15" :: Prelude.ByteString),
        ByteString
"CallAs" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe CallAs
callAs,
        ByteString
"StackSetName" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
stackSetName,
        ByteString
"StackInstanceAccount" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
stackInstanceAccount,
        ByteString
"StackInstanceRegion" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
stackInstanceRegion
      ]

-- | /See:/ 'newDescribeStackInstanceResponse' smart constructor.
data DescribeStackInstanceResponse = DescribeStackInstanceResponse'
  { -- | The stack instance that matches the specified request parameters.
    DescribeStackInstanceResponse -> Maybe StackInstance
stackInstance :: Prelude.Maybe StackInstance,
    -- | The response's http status code.
    DescribeStackInstanceResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DescribeStackInstanceResponse
-> DescribeStackInstanceResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeStackInstanceResponse
-> DescribeStackInstanceResponse -> Bool
$c/= :: DescribeStackInstanceResponse
-> DescribeStackInstanceResponse -> Bool
== :: DescribeStackInstanceResponse
-> DescribeStackInstanceResponse -> Bool
$c== :: DescribeStackInstanceResponse
-> DescribeStackInstanceResponse -> Bool
Prelude.Eq, ReadPrec [DescribeStackInstanceResponse]
ReadPrec DescribeStackInstanceResponse
Int -> ReadS DescribeStackInstanceResponse
ReadS [DescribeStackInstanceResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeStackInstanceResponse]
$creadListPrec :: ReadPrec [DescribeStackInstanceResponse]
readPrec :: ReadPrec DescribeStackInstanceResponse
$creadPrec :: ReadPrec DescribeStackInstanceResponse
readList :: ReadS [DescribeStackInstanceResponse]
$creadList :: ReadS [DescribeStackInstanceResponse]
readsPrec :: Int -> ReadS DescribeStackInstanceResponse
$creadsPrec :: Int -> ReadS DescribeStackInstanceResponse
Prelude.Read, Int -> DescribeStackInstanceResponse -> ShowS
[DescribeStackInstanceResponse] -> ShowS
DescribeStackInstanceResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeStackInstanceResponse] -> ShowS
$cshowList :: [DescribeStackInstanceResponse] -> ShowS
show :: DescribeStackInstanceResponse -> String
$cshow :: DescribeStackInstanceResponse -> String
showsPrec :: Int -> DescribeStackInstanceResponse -> ShowS
$cshowsPrec :: Int -> DescribeStackInstanceResponse -> ShowS
Prelude.Show, forall x.
Rep DescribeStackInstanceResponse x
-> DescribeStackInstanceResponse
forall x.
DescribeStackInstanceResponse
-> Rep DescribeStackInstanceResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeStackInstanceResponse x
-> DescribeStackInstanceResponse
$cfrom :: forall x.
DescribeStackInstanceResponse
-> Rep DescribeStackInstanceResponse x
Prelude.Generic)

-- |
-- Create a value of 'DescribeStackInstanceResponse' 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:
--
-- 'stackInstance', 'describeStackInstanceResponse_stackInstance' - The stack instance that matches the specified request parameters.
--
-- 'httpStatus', 'describeStackInstanceResponse_httpStatus' - The response's http status code.
newDescribeStackInstanceResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DescribeStackInstanceResponse
newDescribeStackInstanceResponse :: Int -> DescribeStackInstanceResponse
newDescribeStackInstanceResponse Int
pHttpStatus_ =
  DescribeStackInstanceResponse'
    { $sel:stackInstance:DescribeStackInstanceResponse' :: Maybe StackInstance
stackInstance =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DescribeStackInstanceResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The stack instance that matches the specified request parameters.
describeStackInstanceResponse_stackInstance :: Lens.Lens' DescribeStackInstanceResponse (Prelude.Maybe StackInstance)
describeStackInstanceResponse_stackInstance :: Lens' DescribeStackInstanceResponse (Maybe StackInstance)
describeStackInstanceResponse_stackInstance = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeStackInstanceResponse' {Maybe StackInstance
stackInstance :: Maybe StackInstance
$sel:stackInstance:DescribeStackInstanceResponse' :: DescribeStackInstanceResponse -> Maybe StackInstance
stackInstance} -> Maybe StackInstance
stackInstance) (\s :: DescribeStackInstanceResponse
s@DescribeStackInstanceResponse' {} Maybe StackInstance
a -> DescribeStackInstanceResponse
s {$sel:stackInstance:DescribeStackInstanceResponse' :: Maybe StackInstance
stackInstance = Maybe StackInstance
a} :: DescribeStackInstanceResponse)

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

instance Prelude.NFData DescribeStackInstanceResponse where
  rnf :: DescribeStackInstanceResponse -> ()
rnf DescribeStackInstanceResponse' {Int
Maybe StackInstance
httpStatus :: Int
stackInstance :: Maybe StackInstance
$sel:httpStatus:DescribeStackInstanceResponse' :: DescribeStackInstanceResponse -> Int
$sel:stackInstance:DescribeStackInstanceResponse' :: DescribeStackInstanceResponse -> Maybe StackInstance
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe StackInstance
stackInstance
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus