{-# 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.EC2.RebootInstances
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Requests a reboot of the specified instances. This operation is
-- asynchronous; it only queues a request to reboot the specified
-- instances. The operation succeeds if the instances are valid and belong
-- to you. Requests to reboot terminated instances are ignored.
--
-- If an instance does not cleanly shut down within a few minutes, Amazon
-- EC2 performs a hard reboot.
--
-- For more information about troubleshooting, see
-- <https://docs.aws.amazon.com/AWSEC2/latest/UserGuide/instance-console.html Troubleshoot an unreachable instance>
-- in the /Amazon EC2 User Guide/.
module Amazonka.EC2.RebootInstances
  ( -- * Creating a Request
    RebootInstances (..),
    newRebootInstances,

    -- * Request Lenses
    rebootInstances_dryRun,
    rebootInstances_instanceIds,

    -- * Destructuring the Response
    RebootInstancesResponse (..),
    newRebootInstancesResponse,
  )
where

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

-- | /See:/ 'newRebootInstances' smart constructor.
data RebootInstances = RebootInstances'
  { -- | Checks whether you have the required permissions for the action, without
    -- actually making the request, and provides an error response. If you have
    -- the required permissions, the error response is @DryRunOperation@.
    -- Otherwise, it is @UnauthorizedOperation@.
    RebootInstances -> Maybe Bool
dryRun :: Prelude.Maybe Prelude.Bool,
    -- | The instance IDs.
    RebootInstances -> [Text]
instanceIds :: [Prelude.Text]
  }
  deriving (RebootInstances -> RebootInstances -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RebootInstances -> RebootInstances -> Bool
$c/= :: RebootInstances -> RebootInstances -> Bool
== :: RebootInstances -> RebootInstances -> Bool
$c== :: RebootInstances -> RebootInstances -> Bool
Prelude.Eq, ReadPrec [RebootInstances]
ReadPrec RebootInstances
Int -> ReadS RebootInstances
ReadS [RebootInstances]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [RebootInstances]
$creadListPrec :: ReadPrec [RebootInstances]
readPrec :: ReadPrec RebootInstances
$creadPrec :: ReadPrec RebootInstances
readList :: ReadS [RebootInstances]
$creadList :: ReadS [RebootInstances]
readsPrec :: Int -> ReadS RebootInstances
$creadsPrec :: Int -> ReadS RebootInstances
Prelude.Read, Int -> RebootInstances -> ShowS
[RebootInstances] -> ShowS
RebootInstances -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RebootInstances] -> ShowS
$cshowList :: [RebootInstances] -> ShowS
show :: RebootInstances -> String
$cshow :: RebootInstances -> String
showsPrec :: Int -> RebootInstances -> ShowS
$cshowsPrec :: Int -> RebootInstances -> ShowS
Prelude.Show, forall x. Rep RebootInstances x -> RebootInstances
forall x. RebootInstances -> Rep RebootInstances x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RebootInstances x -> RebootInstances
$cfrom :: forall x. RebootInstances -> Rep RebootInstances x
Prelude.Generic)

-- |
-- Create a value of 'RebootInstances' 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:
--
-- 'dryRun', 'rebootInstances_dryRun' - Checks whether you have the required permissions for the action, without
-- actually making the request, and provides an error response. If you have
-- the required permissions, the error response is @DryRunOperation@.
-- Otherwise, it is @UnauthorizedOperation@.
--
-- 'instanceIds', 'rebootInstances_instanceIds' - The instance IDs.
newRebootInstances ::
  RebootInstances
newRebootInstances :: RebootInstances
newRebootInstances =
  RebootInstances'
    { $sel:dryRun:RebootInstances' :: Maybe Bool
dryRun = forall a. Maybe a
Prelude.Nothing,
      $sel:instanceIds:RebootInstances' :: [Text]
instanceIds = forall a. Monoid a => a
Prelude.mempty
    }

-- | Checks whether you have the required permissions for the action, without
-- actually making the request, and provides an error response. If you have
-- the required permissions, the error response is @DryRunOperation@.
-- Otherwise, it is @UnauthorizedOperation@.
rebootInstances_dryRun :: Lens.Lens' RebootInstances (Prelude.Maybe Prelude.Bool)
rebootInstances_dryRun :: Lens' RebootInstances (Maybe Bool)
rebootInstances_dryRun = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RebootInstances' {Maybe Bool
dryRun :: Maybe Bool
$sel:dryRun:RebootInstances' :: RebootInstances -> Maybe Bool
dryRun} -> Maybe Bool
dryRun) (\s :: RebootInstances
s@RebootInstances' {} Maybe Bool
a -> RebootInstances
s {$sel:dryRun:RebootInstances' :: Maybe Bool
dryRun = Maybe Bool
a} :: RebootInstances)

-- | The instance IDs.
rebootInstances_instanceIds :: Lens.Lens' RebootInstances [Prelude.Text]
rebootInstances_instanceIds :: Lens' RebootInstances [Text]
rebootInstances_instanceIds = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RebootInstances' {[Text]
instanceIds :: [Text]
$sel:instanceIds:RebootInstances' :: RebootInstances -> [Text]
instanceIds} -> [Text]
instanceIds) (\s :: RebootInstances
s@RebootInstances' {} [Text]
a -> RebootInstances
s {$sel:instanceIds:RebootInstances' :: [Text]
instanceIds = [Text]
a} :: RebootInstances) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

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

instance Prelude.Hashable RebootInstances where
  hashWithSalt :: Int -> RebootInstances -> Int
hashWithSalt Int
_salt RebootInstances' {[Text]
Maybe Bool
instanceIds :: [Text]
dryRun :: Maybe Bool
$sel:instanceIds:RebootInstances' :: RebootInstances -> [Text]
$sel:dryRun:RebootInstances' :: RebootInstances -> Maybe Bool
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
dryRun
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` [Text]
instanceIds

instance Prelude.NFData RebootInstances where
  rnf :: RebootInstances -> ()
rnf RebootInstances' {[Text]
Maybe Bool
instanceIds :: [Text]
dryRun :: Maybe Bool
$sel:instanceIds:RebootInstances' :: RebootInstances -> [Text]
$sel:dryRun:RebootInstances' :: RebootInstances -> Maybe Bool
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
dryRun
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf [Text]
instanceIds

instance Data.ToHeaders RebootInstances where
  toHeaders :: RebootInstances -> [Header]
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

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

instance Data.ToQuery RebootInstances where
  toQuery :: RebootInstances -> QueryString
toQuery RebootInstances' {[Text]
Maybe Bool
instanceIds :: [Text]
dryRun :: Maybe Bool
$sel:instanceIds:RebootInstances' :: RebootInstances -> [Text]
$sel:dryRun:RebootInstances' :: RebootInstances -> Maybe Bool
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"RebootInstances" :: Prelude.ByteString),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2016-11-15" :: Prelude.ByteString),
        ByteString
"DryRun" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Bool
dryRun,
        forall a.
(IsList a, ToQuery (Item a)) =>
ByteString -> a -> QueryString
Data.toQueryList ByteString
"InstanceId" [Text]
instanceIds
      ]

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

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

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