{-# 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.StartStack
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Starts a stack\'s instances.
--
-- __Required Permissions__: To use this action, an IAM user must have a
-- Manage permissions level for the stack, or an attached policy that
-- explicitly grants permissions. For more information on user permissions,
-- see
-- <https://docs.aws.amazon.com/opsworks/latest/userguide/opsworks-security-users.html Managing User Permissions>.
module Amazonka.OpsWorks.StartStack
  ( -- * Creating a Request
    StartStack (..),
    newStartStack,

    -- * Request Lenses
    startStack_stackId,

    -- * Destructuring the Response
    StartStackResponse (..),
    newStartStackResponse,
  )
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:/ 'newStartStack' smart constructor.
data StartStack = StartStack'
  { -- | The stack ID.
    StartStack -> Text
stackId :: Prelude.Text
  }
  deriving (StartStack -> StartStack -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StartStack -> StartStack -> Bool
$c/= :: StartStack -> StartStack -> Bool
== :: StartStack -> StartStack -> Bool
$c== :: StartStack -> StartStack -> Bool
Prelude.Eq, ReadPrec [StartStack]
ReadPrec StartStack
Int -> ReadS StartStack
ReadS [StartStack]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [StartStack]
$creadListPrec :: ReadPrec [StartStack]
readPrec :: ReadPrec StartStack
$creadPrec :: ReadPrec StartStack
readList :: ReadS [StartStack]
$creadList :: ReadS [StartStack]
readsPrec :: Int -> ReadS StartStack
$creadsPrec :: Int -> ReadS StartStack
Prelude.Read, Int -> StartStack -> ShowS
[StartStack] -> ShowS
StartStack -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StartStack] -> ShowS
$cshowList :: [StartStack] -> ShowS
show :: StartStack -> String
$cshow :: StartStack -> String
showsPrec :: Int -> StartStack -> ShowS
$cshowsPrec :: Int -> StartStack -> ShowS
Prelude.Show, forall x. Rep StartStack x -> StartStack
forall x. StartStack -> Rep StartStack x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep StartStack x -> StartStack
$cfrom :: forall x. StartStack -> Rep StartStack x
Prelude.Generic)

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

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

instance Core.AWSRequest StartStack where
  type AWSResponse StartStack = StartStackResponse
  request :: (Service -> Service) -> StartStack -> Request StartStack
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 StartStack
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse StartStack)))
response = forall (m :: * -> *) a.
MonadResource m =>
AWSResponse a
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveNull StartStackResponse
StartStackResponse'

instance Prelude.Hashable StartStack where
  hashWithSalt :: Int -> StartStack -> Int
hashWithSalt Int
_salt StartStack' {Text
stackId :: Text
$sel:stackId:StartStack' :: StartStack -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
stackId

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

instance Data.ToHeaders StartStack where
  toHeaders :: StartStack -> [Header]
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 -> [Header]
Data.=# ( ByteString
"OpsWorks_20130218.StartStack" ::
                          Prelude.ByteString
                      ),
            HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> [Header]
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON StartStack where
  toJSON :: StartStack -> Value
toJSON StartStack' {Text
stackId :: Text
$sel:stackId:StartStack' :: StartStack -> 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 StartStack where
  toPath :: StartStack -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

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

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

-- |
-- Create a value of 'StartStackResponse' 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.
newStartStackResponse ::
  StartStackResponse
newStartStackResponse :: StartStackResponse
newStartStackResponse = StartStackResponse
StartStackResponse'

instance Prelude.NFData StartStackResponse where
  rnf :: StartStackResponse -> ()
rnf StartStackResponse
_ = ()