{-# 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.StartInstance
-- 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 specified instance. For more information, see
-- <https://docs.aws.amazon.com/opsworks/latest/userguide/workinginstances-starting.html Starting, Stopping, and Rebooting 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.StartInstance
  ( -- * Creating a Request
    StartInstance (..),
    newStartInstance,

    -- * Request Lenses
    startInstance_instanceId,

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

-- |
-- Create a value of 'StartInstance' 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:
--
-- 'instanceId', 'startInstance_instanceId' - The instance ID.
newStartInstance ::
  -- | 'instanceId'
  Prelude.Text ->
  StartInstance
newStartInstance :: Text -> StartInstance
newStartInstance Text
pInstanceId_ =
  StartInstance' {$sel:instanceId:StartInstance' :: Text
instanceId = Text
pInstanceId_}

-- | The instance ID.
startInstance_instanceId :: Lens.Lens' StartInstance Prelude.Text
startInstance_instanceId :: Lens' StartInstance Text
startInstance_instanceId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartInstance' {Text
instanceId :: Text
$sel:instanceId:StartInstance' :: StartInstance -> Text
instanceId} -> Text
instanceId) (\s :: StartInstance
s@StartInstance' {} Text
a -> StartInstance
s {$sel:instanceId:StartInstance' :: Text
instanceId = Text
a} :: StartInstance)

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

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

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

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

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

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

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

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

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