{-# 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.DisableImageDeprecation
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Cancels the deprecation of the specified AMI.
--
-- For more information, see
-- <https://docs.aws.amazon.com/AWSEC2/latest/UserGuide/ami-deprecate.html Deprecate an AMI>
-- in the /Amazon EC2 User Guide/.
module Amazonka.EC2.DisableImageDeprecation
  ( -- * Creating a Request
    DisableImageDeprecation (..),
    newDisableImageDeprecation,

    -- * Request Lenses
    disableImageDeprecation_dryRun,
    disableImageDeprecation_imageId,

    -- * Destructuring the Response
    DisableImageDeprecationResponse (..),
    newDisableImageDeprecationResponse,

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

-- |
-- Create a value of 'DisableImageDeprecation' 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', 'disableImageDeprecation_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', 'disableImageDeprecation_imageId' - The ID of the AMI.
newDisableImageDeprecation ::
  -- | 'imageId'
  Prelude.Text ->
  DisableImageDeprecation
newDisableImageDeprecation :: Text -> DisableImageDeprecation
newDisableImageDeprecation Text
pImageId_ =
  DisableImageDeprecation'
    { $sel:dryRun:DisableImageDeprecation' :: Maybe Bool
dryRun = forall a. Maybe a
Prelude.Nothing,
      $sel:imageId:DisableImageDeprecation' :: 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@.
disableImageDeprecation_dryRun :: Lens.Lens' DisableImageDeprecation (Prelude.Maybe Prelude.Bool)
disableImageDeprecation_dryRun :: Lens' DisableImageDeprecation (Maybe Bool)
disableImageDeprecation_dryRun = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DisableImageDeprecation' {Maybe Bool
dryRun :: Maybe Bool
$sel:dryRun:DisableImageDeprecation' :: DisableImageDeprecation -> Maybe Bool
dryRun} -> Maybe Bool
dryRun) (\s :: DisableImageDeprecation
s@DisableImageDeprecation' {} Maybe Bool
a -> DisableImageDeprecation
s {$sel:dryRun:DisableImageDeprecation' :: Maybe Bool
dryRun = Maybe Bool
a} :: DisableImageDeprecation)

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

instance Core.AWSRequest DisableImageDeprecation where
  type
    AWSResponse DisableImageDeprecation =
      DisableImageDeprecationResponse
  request :: (Service -> Service)
-> DisableImageDeprecation -> Request DisableImageDeprecation
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 DisableImageDeprecation
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DisableImageDeprecation)))
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 -> DisableImageDeprecationResponse
DisableImageDeprecationResponse'
            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 DisableImageDeprecation where
  hashWithSalt :: Int -> DisableImageDeprecation -> Int
hashWithSalt Int
_salt DisableImageDeprecation' {Maybe Bool
Text
imageId :: Text
dryRun :: Maybe Bool
$sel:imageId:DisableImageDeprecation' :: DisableImageDeprecation -> Text
$sel:dryRun:DisableImageDeprecation' :: DisableImageDeprecation -> 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 DisableImageDeprecation where
  rnf :: DisableImageDeprecation -> ()
rnf DisableImageDeprecation' {Maybe Bool
Text
imageId :: Text
dryRun :: Maybe Bool
$sel:imageId:DisableImageDeprecation' :: DisableImageDeprecation -> Text
$sel:dryRun:DisableImageDeprecation' :: DisableImageDeprecation -> 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 DisableImageDeprecation where
  toHeaders :: DisableImageDeprecation -> ResponseHeaders
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

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

instance Data.ToQuery DisableImageDeprecation where
  toQuery :: DisableImageDeprecation -> QueryString
toQuery DisableImageDeprecation' {Maybe Bool
Text
imageId :: Text
dryRun :: Maybe Bool
$sel:imageId:DisableImageDeprecation' :: DisableImageDeprecation -> Text
$sel:dryRun:DisableImageDeprecation' :: DisableImageDeprecation -> Maybe Bool
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"DisableImageDeprecation" :: 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:/ 'newDisableImageDeprecationResponse' smart constructor.
data DisableImageDeprecationResponse = DisableImageDeprecationResponse'
  { -- | Returns @true@ if the request succeeds; otherwise, it returns an error.
    DisableImageDeprecationResponse -> Maybe Bool
return' :: Prelude.Maybe Prelude.Bool,
    -- | The response's http status code.
    DisableImageDeprecationResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DisableImageDeprecationResponse
-> DisableImageDeprecationResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DisableImageDeprecationResponse
-> DisableImageDeprecationResponse -> Bool
$c/= :: DisableImageDeprecationResponse
-> DisableImageDeprecationResponse -> Bool
== :: DisableImageDeprecationResponse
-> DisableImageDeprecationResponse -> Bool
$c== :: DisableImageDeprecationResponse
-> DisableImageDeprecationResponse -> Bool
Prelude.Eq, ReadPrec [DisableImageDeprecationResponse]
ReadPrec DisableImageDeprecationResponse
Int -> ReadS DisableImageDeprecationResponse
ReadS [DisableImageDeprecationResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DisableImageDeprecationResponse]
$creadListPrec :: ReadPrec [DisableImageDeprecationResponse]
readPrec :: ReadPrec DisableImageDeprecationResponse
$creadPrec :: ReadPrec DisableImageDeprecationResponse
readList :: ReadS [DisableImageDeprecationResponse]
$creadList :: ReadS [DisableImageDeprecationResponse]
readsPrec :: Int -> ReadS DisableImageDeprecationResponse
$creadsPrec :: Int -> ReadS DisableImageDeprecationResponse
Prelude.Read, Int -> DisableImageDeprecationResponse -> ShowS
[DisableImageDeprecationResponse] -> ShowS
DisableImageDeprecationResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DisableImageDeprecationResponse] -> ShowS
$cshowList :: [DisableImageDeprecationResponse] -> ShowS
show :: DisableImageDeprecationResponse -> String
$cshow :: DisableImageDeprecationResponse -> String
showsPrec :: Int -> DisableImageDeprecationResponse -> ShowS
$cshowsPrec :: Int -> DisableImageDeprecationResponse -> ShowS
Prelude.Show, forall x.
Rep DisableImageDeprecationResponse x
-> DisableImageDeprecationResponse
forall x.
DisableImageDeprecationResponse
-> Rep DisableImageDeprecationResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DisableImageDeprecationResponse x
-> DisableImageDeprecationResponse
$cfrom :: forall x.
DisableImageDeprecationResponse
-> Rep DisableImageDeprecationResponse x
Prelude.Generic)

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

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

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

instance
  Prelude.NFData
    DisableImageDeprecationResponse
  where
  rnf :: DisableImageDeprecationResponse -> ()
rnf DisableImageDeprecationResponse' {Int
Maybe Bool
httpStatus :: Int
return' :: Maybe Bool
$sel:httpStatus:DisableImageDeprecationResponse' :: DisableImageDeprecationResponse -> Int
$sel:return':DisableImageDeprecationResponse' :: DisableImageDeprecationResponse -> 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