{-# 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.OpsWorks.DescribeStackSummary
-- 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 the number of layers and apps in a specified stack, and the
-- number of instances in each state, such as @running_setup@ or @online@.
--
-- __Required Permissions__: To use this action, an IAM user must have a
-- Show, Deploy, or Manage permissions level for the stack, or an attached
-- policy that explicitly grants permissions. For more information about
-- user permissions, see
-- <https://docs.aws.amazon.com/opsworks/latest/userguide/opsworks-security-users.html Managing User Permissions>.
module Amazonka.OpsWorks.DescribeStackSummary
  ( -- * Creating a Request
    DescribeStackSummary (..),
    newDescribeStackSummary,

    -- * Request Lenses
    describeStackSummary_stackId,

    -- * Destructuring the Response
    DescribeStackSummaryResponse (..),
    newDescribeStackSummaryResponse,

    -- * Response Lenses
    describeStackSummaryResponse_stackSummary,
    describeStackSummaryResponse_httpStatus,
  )
where

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

-- | /See:/ 'newDescribeStackSummary' smart constructor.
data DescribeStackSummary = DescribeStackSummary'
  { -- | The stack ID.
    DescribeStackSummary -> Text
stackId :: Prelude.Text
  }
  deriving (DescribeStackSummary -> DescribeStackSummary -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeStackSummary -> DescribeStackSummary -> Bool
$c/= :: DescribeStackSummary -> DescribeStackSummary -> Bool
== :: DescribeStackSummary -> DescribeStackSummary -> Bool
$c== :: DescribeStackSummary -> DescribeStackSummary -> Bool
Prelude.Eq, ReadPrec [DescribeStackSummary]
ReadPrec DescribeStackSummary
Int -> ReadS DescribeStackSummary
ReadS [DescribeStackSummary]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeStackSummary]
$creadListPrec :: ReadPrec [DescribeStackSummary]
readPrec :: ReadPrec DescribeStackSummary
$creadPrec :: ReadPrec DescribeStackSummary
readList :: ReadS [DescribeStackSummary]
$creadList :: ReadS [DescribeStackSummary]
readsPrec :: Int -> ReadS DescribeStackSummary
$creadsPrec :: Int -> ReadS DescribeStackSummary
Prelude.Read, Int -> DescribeStackSummary -> ShowS
[DescribeStackSummary] -> ShowS
DescribeStackSummary -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeStackSummary] -> ShowS
$cshowList :: [DescribeStackSummary] -> ShowS
show :: DescribeStackSummary -> String
$cshow :: DescribeStackSummary -> String
showsPrec :: Int -> DescribeStackSummary -> ShowS
$cshowsPrec :: Int -> DescribeStackSummary -> ShowS
Prelude.Show, forall x. Rep DescribeStackSummary x -> DescribeStackSummary
forall x. DescribeStackSummary -> Rep DescribeStackSummary x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DescribeStackSummary x -> DescribeStackSummary
$cfrom :: forall x. DescribeStackSummary -> Rep DescribeStackSummary x
Prelude.Generic)

-- |
-- Create a value of 'DescribeStackSummary' 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:
--
-- 'stackId', 'describeStackSummary_stackId' - The stack ID.
newDescribeStackSummary ::
  -- | 'stackId'
  Prelude.Text ->
  DescribeStackSummary
newDescribeStackSummary :: Text -> DescribeStackSummary
newDescribeStackSummary Text
pStackId_ =
  DescribeStackSummary' {$sel:stackId:DescribeStackSummary' :: Text
stackId = Text
pStackId_}

-- | The stack ID.
describeStackSummary_stackId :: Lens.Lens' DescribeStackSummary Prelude.Text
describeStackSummary_stackId :: Lens' DescribeStackSummary Text
describeStackSummary_stackId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeStackSummary' {Text
stackId :: Text
$sel:stackId:DescribeStackSummary' :: DescribeStackSummary -> Text
stackId} -> Text
stackId) (\s :: DescribeStackSummary
s@DescribeStackSummary' {} Text
a -> DescribeStackSummary
s {$sel:stackId:DescribeStackSummary' :: Text
stackId = Text
a} :: DescribeStackSummary)

instance Core.AWSRequest DescribeStackSummary where
  type
    AWSResponse DescribeStackSummary =
      DescribeStackSummaryResponse
  request :: (Service -> Service)
-> DescribeStackSummary -> Request DescribeStackSummary
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 DescribeStackSummary
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DescribeStackSummary)))
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 StackSummary -> Int -> DescribeStackSummaryResponse
DescribeStackSummaryResponse'
            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
"StackSummary")
            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 DescribeStackSummary where
  hashWithSalt :: Int -> DescribeStackSummary -> Int
hashWithSalt Int
_salt DescribeStackSummary' {Text
stackId :: Text
$sel:stackId:DescribeStackSummary' :: DescribeStackSummary -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
stackId

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

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

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

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

-- | Contains the response to a @DescribeStackSummary@ request.
--
-- /See:/ 'newDescribeStackSummaryResponse' smart constructor.
data DescribeStackSummaryResponse = DescribeStackSummaryResponse'
  { -- | A @StackSummary@ object that contains the results.
    DescribeStackSummaryResponse -> Maybe StackSummary
stackSummary :: Prelude.Maybe StackSummary,
    -- | The response's http status code.
    DescribeStackSummaryResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DescribeStackSummaryResponse
-> DescribeStackSummaryResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeStackSummaryResponse
-> DescribeStackSummaryResponse -> Bool
$c/= :: DescribeStackSummaryResponse
-> DescribeStackSummaryResponse -> Bool
== :: DescribeStackSummaryResponse
-> DescribeStackSummaryResponse -> Bool
$c== :: DescribeStackSummaryResponse
-> DescribeStackSummaryResponse -> Bool
Prelude.Eq, ReadPrec [DescribeStackSummaryResponse]
ReadPrec DescribeStackSummaryResponse
Int -> ReadS DescribeStackSummaryResponse
ReadS [DescribeStackSummaryResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeStackSummaryResponse]
$creadListPrec :: ReadPrec [DescribeStackSummaryResponse]
readPrec :: ReadPrec DescribeStackSummaryResponse
$creadPrec :: ReadPrec DescribeStackSummaryResponse
readList :: ReadS [DescribeStackSummaryResponse]
$creadList :: ReadS [DescribeStackSummaryResponse]
readsPrec :: Int -> ReadS DescribeStackSummaryResponse
$creadsPrec :: Int -> ReadS DescribeStackSummaryResponse
Prelude.Read, Int -> DescribeStackSummaryResponse -> ShowS
[DescribeStackSummaryResponse] -> ShowS
DescribeStackSummaryResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeStackSummaryResponse] -> ShowS
$cshowList :: [DescribeStackSummaryResponse] -> ShowS
show :: DescribeStackSummaryResponse -> String
$cshow :: DescribeStackSummaryResponse -> String
showsPrec :: Int -> DescribeStackSummaryResponse -> ShowS
$cshowsPrec :: Int -> DescribeStackSummaryResponse -> ShowS
Prelude.Show, forall x.
Rep DescribeStackSummaryResponse x -> DescribeStackSummaryResponse
forall x.
DescribeStackSummaryResponse -> Rep DescribeStackSummaryResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeStackSummaryResponse x -> DescribeStackSummaryResponse
$cfrom :: forall x.
DescribeStackSummaryResponse -> Rep DescribeStackSummaryResponse x
Prelude.Generic)

-- |
-- Create a value of 'DescribeStackSummaryResponse' 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:
--
-- 'stackSummary', 'describeStackSummaryResponse_stackSummary' - A @StackSummary@ object that contains the results.
--
-- 'httpStatus', 'describeStackSummaryResponse_httpStatus' - The response's http status code.
newDescribeStackSummaryResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DescribeStackSummaryResponse
newDescribeStackSummaryResponse :: Int -> DescribeStackSummaryResponse
newDescribeStackSummaryResponse Int
pHttpStatus_ =
  DescribeStackSummaryResponse'
    { $sel:stackSummary:DescribeStackSummaryResponse' :: Maybe StackSummary
stackSummary =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DescribeStackSummaryResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | A @StackSummary@ object that contains the results.
describeStackSummaryResponse_stackSummary :: Lens.Lens' DescribeStackSummaryResponse (Prelude.Maybe StackSummary)
describeStackSummaryResponse_stackSummary :: Lens' DescribeStackSummaryResponse (Maybe StackSummary)
describeStackSummaryResponse_stackSummary = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeStackSummaryResponse' {Maybe StackSummary
stackSummary :: Maybe StackSummary
$sel:stackSummary:DescribeStackSummaryResponse' :: DescribeStackSummaryResponse -> Maybe StackSummary
stackSummary} -> Maybe StackSummary
stackSummary) (\s :: DescribeStackSummaryResponse
s@DescribeStackSummaryResponse' {} Maybe StackSummary
a -> DescribeStackSummaryResponse
s {$sel:stackSummary:DescribeStackSummaryResponse' :: Maybe StackSummary
stackSummary = Maybe StackSummary
a} :: DescribeStackSummaryResponse)

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

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