{-# 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.RestoreImageFromRecycleBin
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Restores an AMI from the Recycle Bin. For more information, see
-- <https://docs.aws.amazon.com/AWSEC2/latest/UserGuide/recycle-bin.html Recycle Bin>
-- in the /Amazon EC2 User Guide/.
module Amazonka.EC2.RestoreImageFromRecycleBin
  ( -- * Creating a Request
    RestoreImageFromRecycleBin (..),
    newRestoreImageFromRecycleBin,

    -- * Request Lenses
    restoreImageFromRecycleBin_dryRun,
    restoreImageFromRecycleBin_imageId,

    -- * Destructuring the Response
    RestoreImageFromRecycleBinResponse (..),
    newRestoreImageFromRecycleBinResponse,

    -- * Response Lenses
    restoreImageFromRecycleBinResponse_return,
    restoreImageFromRecycleBinResponse_httpStatus,
  )
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:/ 'newRestoreImageFromRecycleBin' smart constructor.
data RestoreImageFromRecycleBin = RestoreImageFromRecycleBin'
  { -- | 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@.
    RestoreImageFromRecycleBin -> Maybe Bool
dryRun :: Prelude.Maybe Prelude.Bool,
    -- | The ID of the AMI to restore.
    RestoreImageFromRecycleBin -> Text
imageId :: Prelude.Text
  }
  deriving (RestoreImageFromRecycleBin -> RestoreImageFromRecycleBin -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RestoreImageFromRecycleBin -> RestoreImageFromRecycleBin -> Bool
$c/= :: RestoreImageFromRecycleBin -> RestoreImageFromRecycleBin -> Bool
== :: RestoreImageFromRecycleBin -> RestoreImageFromRecycleBin -> Bool
$c== :: RestoreImageFromRecycleBin -> RestoreImageFromRecycleBin -> Bool
Prelude.Eq, ReadPrec [RestoreImageFromRecycleBin]
ReadPrec RestoreImageFromRecycleBin
Int -> ReadS RestoreImageFromRecycleBin
ReadS [RestoreImageFromRecycleBin]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [RestoreImageFromRecycleBin]
$creadListPrec :: ReadPrec [RestoreImageFromRecycleBin]
readPrec :: ReadPrec RestoreImageFromRecycleBin
$creadPrec :: ReadPrec RestoreImageFromRecycleBin
readList :: ReadS [RestoreImageFromRecycleBin]
$creadList :: ReadS [RestoreImageFromRecycleBin]
readsPrec :: Int -> ReadS RestoreImageFromRecycleBin
$creadsPrec :: Int -> ReadS RestoreImageFromRecycleBin
Prelude.Read, Int -> RestoreImageFromRecycleBin -> ShowS
[RestoreImageFromRecycleBin] -> ShowS
RestoreImageFromRecycleBin -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RestoreImageFromRecycleBin] -> ShowS
$cshowList :: [RestoreImageFromRecycleBin] -> ShowS
show :: RestoreImageFromRecycleBin -> String
$cshow :: RestoreImageFromRecycleBin -> String
showsPrec :: Int -> RestoreImageFromRecycleBin -> ShowS
$cshowsPrec :: Int -> RestoreImageFromRecycleBin -> ShowS
Prelude.Show, forall x.
Rep RestoreImageFromRecycleBin x -> RestoreImageFromRecycleBin
forall x.
RestoreImageFromRecycleBin -> Rep RestoreImageFromRecycleBin x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep RestoreImageFromRecycleBin x -> RestoreImageFromRecycleBin
$cfrom :: forall x.
RestoreImageFromRecycleBin -> Rep RestoreImageFromRecycleBin x
Prelude.Generic)

-- |
-- Create a value of 'RestoreImageFromRecycleBin' 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', 'restoreImageFromRecycleBin_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@.
--
-- 'imageId', 'restoreImageFromRecycleBin_imageId' - The ID of the AMI to restore.
newRestoreImageFromRecycleBin ::
  -- | 'imageId'
  Prelude.Text ->
  RestoreImageFromRecycleBin
newRestoreImageFromRecycleBin :: Text -> RestoreImageFromRecycleBin
newRestoreImageFromRecycleBin Text
pImageId_ =
  RestoreImageFromRecycleBin'
    { $sel:dryRun:RestoreImageFromRecycleBin' :: Maybe Bool
dryRun =
        forall a. Maybe a
Prelude.Nothing,
      $sel:imageId:RestoreImageFromRecycleBin' :: Text
imageId = Text
pImageId_
    }

-- | 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@.
restoreImageFromRecycleBin_dryRun :: Lens.Lens' RestoreImageFromRecycleBin (Prelude.Maybe Prelude.Bool)
restoreImageFromRecycleBin_dryRun :: Lens' RestoreImageFromRecycleBin (Maybe Bool)
restoreImageFromRecycleBin_dryRun = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RestoreImageFromRecycleBin' {Maybe Bool
dryRun :: Maybe Bool
$sel:dryRun:RestoreImageFromRecycleBin' :: RestoreImageFromRecycleBin -> Maybe Bool
dryRun} -> Maybe Bool
dryRun) (\s :: RestoreImageFromRecycleBin
s@RestoreImageFromRecycleBin' {} Maybe Bool
a -> RestoreImageFromRecycleBin
s {$sel:dryRun:RestoreImageFromRecycleBin' :: Maybe Bool
dryRun = Maybe Bool
a} :: RestoreImageFromRecycleBin)

-- | The ID of the AMI to restore.
restoreImageFromRecycleBin_imageId :: Lens.Lens' RestoreImageFromRecycleBin Prelude.Text
restoreImageFromRecycleBin_imageId :: Lens' RestoreImageFromRecycleBin Text
restoreImageFromRecycleBin_imageId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RestoreImageFromRecycleBin' {Text
imageId :: Text
$sel:imageId:RestoreImageFromRecycleBin' :: RestoreImageFromRecycleBin -> Text
imageId} -> Text
imageId) (\s :: RestoreImageFromRecycleBin
s@RestoreImageFromRecycleBin' {} Text
a -> RestoreImageFromRecycleBin
s {$sel:imageId:RestoreImageFromRecycleBin' :: Text
imageId = Text
a} :: RestoreImageFromRecycleBin)

instance Core.AWSRequest RestoreImageFromRecycleBin where
  type
    AWSResponse RestoreImageFromRecycleBin =
      RestoreImageFromRecycleBinResponse
  request :: (Service -> Service)
-> RestoreImageFromRecycleBin -> Request RestoreImageFromRecycleBin
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 RestoreImageFromRecycleBin
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse RestoreImageFromRecycleBin)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> [Node] -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveXML
      ( \Int
s ResponseHeaders
h [Node]
x ->
          Maybe Bool -> Int -> RestoreImageFromRecycleBinResponse
RestoreImageFromRecycleBinResponse'
            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
"return")
            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 RestoreImageFromRecycleBin where
  hashWithSalt :: Int -> RestoreImageFromRecycleBin -> Int
hashWithSalt Int
_salt RestoreImageFromRecycleBin' {Maybe Bool
Text
imageId :: Text
dryRun :: Maybe Bool
$sel:imageId:RestoreImageFromRecycleBin' :: RestoreImageFromRecycleBin -> Text
$sel:dryRun:RestoreImageFromRecycleBin' :: RestoreImageFromRecycleBin -> 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
imageId

instance Prelude.NFData RestoreImageFromRecycleBin where
  rnf :: RestoreImageFromRecycleBin -> ()
rnf RestoreImageFromRecycleBin' {Maybe Bool
Text
imageId :: Text
dryRun :: Maybe Bool
$sel:imageId:RestoreImageFromRecycleBin' :: RestoreImageFromRecycleBin -> Text
$sel:dryRun:RestoreImageFromRecycleBin' :: RestoreImageFromRecycleBin -> 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
imageId

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

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

instance Data.ToQuery RestoreImageFromRecycleBin where
  toQuery :: RestoreImageFromRecycleBin -> QueryString
toQuery RestoreImageFromRecycleBin' {Maybe Bool
Text
imageId :: Text
dryRun :: Maybe Bool
$sel:imageId:RestoreImageFromRecycleBin' :: RestoreImageFromRecycleBin -> Text
$sel:dryRun:RestoreImageFromRecycleBin' :: RestoreImageFromRecycleBin -> Maybe Bool
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"RestoreImageFromRecycleBin" :: 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,
        ByteString
"ImageId" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
imageId
      ]

-- | /See:/ 'newRestoreImageFromRecycleBinResponse' smart constructor.
data RestoreImageFromRecycleBinResponse = RestoreImageFromRecycleBinResponse'
  { -- | Returns @true@ if the request succeeds; otherwise, it returns an error.
    RestoreImageFromRecycleBinResponse -> Maybe Bool
return' :: Prelude.Maybe Prelude.Bool,
    -- | The response's http status code.
    RestoreImageFromRecycleBinResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (RestoreImageFromRecycleBinResponse
-> RestoreImageFromRecycleBinResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RestoreImageFromRecycleBinResponse
-> RestoreImageFromRecycleBinResponse -> Bool
$c/= :: RestoreImageFromRecycleBinResponse
-> RestoreImageFromRecycleBinResponse -> Bool
== :: RestoreImageFromRecycleBinResponse
-> RestoreImageFromRecycleBinResponse -> Bool
$c== :: RestoreImageFromRecycleBinResponse
-> RestoreImageFromRecycleBinResponse -> Bool
Prelude.Eq, ReadPrec [RestoreImageFromRecycleBinResponse]
ReadPrec RestoreImageFromRecycleBinResponse
Int -> ReadS RestoreImageFromRecycleBinResponse
ReadS [RestoreImageFromRecycleBinResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [RestoreImageFromRecycleBinResponse]
$creadListPrec :: ReadPrec [RestoreImageFromRecycleBinResponse]
readPrec :: ReadPrec RestoreImageFromRecycleBinResponse
$creadPrec :: ReadPrec RestoreImageFromRecycleBinResponse
readList :: ReadS [RestoreImageFromRecycleBinResponse]
$creadList :: ReadS [RestoreImageFromRecycleBinResponse]
readsPrec :: Int -> ReadS RestoreImageFromRecycleBinResponse
$creadsPrec :: Int -> ReadS RestoreImageFromRecycleBinResponse
Prelude.Read, Int -> RestoreImageFromRecycleBinResponse -> ShowS
[RestoreImageFromRecycleBinResponse] -> ShowS
RestoreImageFromRecycleBinResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RestoreImageFromRecycleBinResponse] -> ShowS
$cshowList :: [RestoreImageFromRecycleBinResponse] -> ShowS
show :: RestoreImageFromRecycleBinResponse -> String
$cshow :: RestoreImageFromRecycleBinResponse -> String
showsPrec :: Int -> RestoreImageFromRecycleBinResponse -> ShowS
$cshowsPrec :: Int -> RestoreImageFromRecycleBinResponse -> ShowS
Prelude.Show, forall x.
Rep RestoreImageFromRecycleBinResponse x
-> RestoreImageFromRecycleBinResponse
forall x.
RestoreImageFromRecycleBinResponse
-> Rep RestoreImageFromRecycleBinResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep RestoreImageFromRecycleBinResponse x
-> RestoreImageFromRecycleBinResponse
$cfrom :: forall x.
RestoreImageFromRecycleBinResponse
-> Rep RestoreImageFromRecycleBinResponse x
Prelude.Generic)

-- |
-- Create a value of 'RestoreImageFromRecycleBinResponse' 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:
--
-- 'return'', 'restoreImageFromRecycleBinResponse_return' - Returns @true@ if the request succeeds; otherwise, it returns an error.
--
-- 'httpStatus', 'restoreImageFromRecycleBinResponse_httpStatus' - The response's http status code.
newRestoreImageFromRecycleBinResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  RestoreImageFromRecycleBinResponse
newRestoreImageFromRecycleBinResponse :: Int -> RestoreImageFromRecycleBinResponse
newRestoreImageFromRecycleBinResponse Int
pHttpStatus_ =
  RestoreImageFromRecycleBinResponse'
    { $sel:return':RestoreImageFromRecycleBinResponse' :: Maybe Bool
return' =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:RestoreImageFromRecycleBinResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Returns @true@ if the request succeeds; otherwise, it returns an error.
restoreImageFromRecycleBinResponse_return :: Lens.Lens' RestoreImageFromRecycleBinResponse (Prelude.Maybe Prelude.Bool)
restoreImageFromRecycleBinResponse_return :: Lens' RestoreImageFromRecycleBinResponse (Maybe Bool)
restoreImageFromRecycleBinResponse_return = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RestoreImageFromRecycleBinResponse' {Maybe Bool
return' :: Maybe Bool
$sel:return':RestoreImageFromRecycleBinResponse' :: RestoreImageFromRecycleBinResponse -> Maybe Bool
return'} -> Maybe Bool
return') (\s :: RestoreImageFromRecycleBinResponse
s@RestoreImageFromRecycleBinResponse' {} Maybe Bool
a -> RestoreImageFromRecycleBinResponse
s {$sel:return':RestoreImageFromRecycleBinResponse' :: Maybe Bool
return' = Maybe Bool
a} :: RestoreImageFromRecycleBinResponse)

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

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