{-# 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.EnableImageDeprecation
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Enables deprecation of the specified AMI at the specified date and time.
--
-- 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.EnableImageDeprecation
  ( -- * Creating a Request
    EnableImageDeprecation (..),
    newEnableImageDeprecation,

    -- * Request Lenses
    enableImageDeprecation_dryRun,
    enableImageDeprecation_imageId,
    enableImageDeprecation_deprecateAt,

    -- * Destructuring the Response
    EnableImageDeprecationResponse (..),
    newEnableImageDeprecationResponse,

    -- * Response Lenses
    enableImageDeprecationResponse_return,
    enableImageDeprecationResponse_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:/ 'newEnableImageDeprecation' smart constructor.
data EnableImageDeprecation = EnableImageDeprecation'
  { -- | 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@.
    EnableImageDeprecation -> Maybe Bool
dryRun :: Prelude.Maybe Prelude.Bool,
    -- | The ID of the AMI.
    EnableImageDeprecation -> Text
imageId :: Prelude.Text,
    -- | The date and time to deprecate the AMI, in UTC, in the following format:
    -- /YYYY/-/MM/-/DD/T/HH/:/MM/:/SS/Z. If you specify a value for seconds,
    -- Amazon EC2 rounds the seconds to the nearest minute.
    --
    -- You can’t specify a date in the past. The upper limit for @DeprecateAt@
    -- is 10 years from now, except for public AMIs, where the upper limit is 2
    -- years from the creation date.
    EnableImageDeprecation -> ISO8601
deprecateAt :: Data.ISO8601
  }
  deriving (EnableImageDeprecation -> EnableImageDeprecation -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EnableImageDeprecation -> EnableImageDeprecation -> Bool
$c/= :: EnableImageDeprecation -> EnableImageDeprecation -> Bool
== :: EnableImageDeprecation -> EnableImageDeprecation -> Bool
$c== :: EnableImageDeprecation -> EnableImageDeprecation -> Bool
Prelude.Eq, ReadPrec [EnableImageDeprecation]
ReadPrec EnableImageDeprecation
Int -> ReadS EnableImageDeprecation
ReadS [EnableImageDeprecation]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [EnableImageDeprecation]
$creadListPrec :: ReadPrec [EnableImageDeprecation]
readPrec :: ReadPrec EnableImageDeprecation
$creadPrec :: ReadPrec EnableImageDeprecation
readList :: ReadS [EnableImageDeprecation]
$creadList :: ReadS [EnableImageDeprecation]
readsPrec :: Int -> ReadS EnableImageDeprecation
$creadsPrec :: Int -> ReadS EnableImageDeprecation
Prelude.Read, Int -> EnableImageDeprecation -> ShowS
[EnableImageDeprecation] -> ShowS
EnableImageDeprecation -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [EnableImageDeprecation] -> ShowS
$cshowList :: [EnableImageDeprecation] -> ShowS
show :: EnableImageDeprecation -> String
$cshow :: EnableImageDeprecation -> String
showsPrec :: Int -> EnableImageDeprecation -> ShowS
$cshowsPrec :: Int -> EnableImageDeprecation -> ShowS
Prelude.Show, forall x. Rep EnableImageDeprecation x -> EnableImageDeprecation
forall x. EnableImageDeprecation -> Rep EnableImageDeprecation x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep EnableImageDeprecation x -> EnableImageDeprecation
$cfrom :: forall x. EnableImageDeprecation -> Rep EnableImageDeprecation x
Prelude.Generic)

-- |
-- Create a value of 'EnableImageDeprecation' 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', 'enableImageDeprecation_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', 'enableImageDeprecation_imageId' - The ID of the AMI.
--
-- 'deprecateAt', 'enableImageDeprecation_deprecateAt' - The date and time to deprecate the AMI, in UTC, in the following format:
-- /YYYY/-/MM/-/DD/T/HH/:/MM/:/SS/Z. If you specify a value for seconds,
-- Amazon EC2 rounds the seconds to the nearest minute.
--
-- You can’t specify a date in the past. The upper limit for @DeprecateAt@
-- is 10 years from now, except for public AMIs, where the upper limit is 2
-- years from the creation date.
newEnableImageDeprecation ::
  -- | 'imageId'
  Prelude.Text ->
  -- | 'deprecateAt'
  Prelude.UTCTime ->
  EnableImageDeprecation
newEnableImageDeprecation :: Text -> UTCTime -> EnableImageDeprecation
newEnableImageDeprecation Text
pImageId_ UTCTime
pDeprecateAt_ =
  EnableImageDeprecation'
    { $sel:dryRun:EnableImageDeprecation' :: Maybe Bool
dryRun = forall a. Maybe a
Prelude.Nothing,
      $sel:imageId:EnableImageDeprecation' :: Text
imageId = Text
pImageId_,
      $sel:deprecateAt:EnableImageDeprecation' :: ISO8601
deprecateAt = forall (a :: Format). Iso' (Time a) UTCTime
Data._Time forall t b. AReview t b -> b -> t
Lens.# UTCTime
pDeprecateAt_
    }

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

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

-- | The date and time to deprecate the AMI, in UTC, in the following format:
-- /YYYY/-/MM/-/DD/T/HH/:/MM/:/SS/Z. If you specify a value for seconds,
-- Amazon EC2 rounds the seconds to the nearest minute.
--
-- You can’t specify a date in the past. The upper limit for @DeprecateAt@
-- is 10 years from now, except for public AMIs, where the upper limit is 2
-- years from the creation date.
enableImageDeprecation_deprecateAt :: Lens.Lens' EnableImageDeprecation Prelude.UTCTime
enableImageDeprecation_deprecateAt :: Lens' EnableImageDeprecation UTCTime
enableImageDeprecation_deprecateAt = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\EnableImageDeprecation' {ISO8601
deprecateAt :: ISO8601
$sel:deprecateAt:EnableImageDeprecation' :: EnableImageDeprecation -> ISO8601
deprecateAt} -> ISO8601
deprecateAt) (\s :: EnableImageDeprecation
s@EnableImageDeprecation' {} ISO8601
a -> EnableImageDeprecation
s {$sel:deprecateAt:EnableImageDeprecation' :: ISO8601
deprecateAt = ISO8601
a} :: EnableImageDeprecation) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (a :: Format). Iso' (Time a) UTCTime
Data._Time

instance Core.AWSRequest EnableImageDeprecation where
  type
    AWSResponse EnableImageDeprecation =
      EnableImageDeprecationResponse
  request :: (Service -> Service)
-> EnableImageDeprecation -> Request EnableImageDeprecation
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 EnableImageDeprecation
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse EnableImageDeprecation)))
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 -> EnableImageDeprecationResponse
EnableImageDeprecationResponse'
            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 EnableImageDeprecation where
  hashWithSalt :: Int -> EnableImageDeprecation -> Int
hashWithSalt Int
_salt EnableImageDeprecation' {Maybe Bool
Text
ISO8601
deprecateAt :: ISO8601
imageId :: Text
dryRun :: Maybe Bool
$sel:deprecateAt:EnableImageDeprecation' :: EnableImageDeprecation -> ISO8601
$sel:imageId:EnableImageDeprecation' :: EnableImageDeprecation -> Text
$sel:dryRun:EnableImageDeprecation' :: EnableImageDeprecation -> 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
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` ISO8601
deprecateAt

instance Prelude.NFData EnableImageDeprecation where
  rnf :: EnableImageDeprecation -> ()
rnf EnableImageDeprecation' {Maybe Bool
Text
ISO8601
deprecateAt :: ISO8601
imageId :: Text
dryRun :: Maybe Bool
$sel:deprecateAt:EnableImageDeprecation' :: EnableImageDeprecation -> ISO8601
$sel:imageId:EnableImageDeprecation' :: EnableImageDeprecation -> Text
$sel:dryRun:EnableImageDeprecation' :: EnableImageDeprecation -> 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
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf ISO8601
deprecateAt

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

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

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

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

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

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

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

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