{-# 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.CancelImageLaunchPermission
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Removes your Amazon Web Services account from the launch permissions for
-- the specified AMI. For more information, see
-- <https://docs.aws.amazon.com/ Cancel having an AMI shared with your Amazon Web Services account>
-- in the /Amazon EC2 User Guide/.
module Amazonka.EC2.CancelImageLaunchPermission
  ( -- * Creating a Request
    CancelImageLaunchPermission (..),
    newCancelImageLaunchPermission,

    -- * Request Lenses
    cancelImageLaunchPermission_dryRun,
    cancelImageLaunchPermission_imageId,

    -- * Destructuring the Response
    CancelImageLaunchPermissionResponse (..),
    newCancelImageLaunchPermissionResponse,

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

-- |
-- Create a value of 'CancelImageLaunchPermission' 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', 'cancelImageLaunchPermission_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', 'cancelImageLaunchPermission_imageId' - The ID of the AMI that was shared with your Amazon Web Services account.
newCancelImageLaunchPermission ::
  -- | 'imageId'
  Prelude.Text ->
  CancelImageLaunchPermission
newCancelImageLaunchPermission :: Text -> CancelImageLaunchPermission
newCancelImageLaunchPermission Text
pImageId_ =
  CancelImageLaunchPermission'
    { $sel:dryRun:CancelImageLaunchPermission' :: Maybe Bool
dryRun =
        forall a. Maybe a
Prelude.Nothing,
      $sel:imageId:CancelImageLaunchPermission' :: 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@.
cancelImageLaunchPermission_dryRun :: Lens.Lens' CancelImageLaunchPermission (Prelude.Maybe Prelude.Bool)
cancelImageLaunchPermission_dryRun :: Lens' CancelImageLaunchPermission (Maybe Bool)
cancelImageLaunchPermission_dryRun = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CancelImageLaunchPermission' {Maybe Bool
dryRun :: Maybe Bool
$sel:dryRun:CancelImageLaunchPermission' :: CancelImageLaunchPermission -> Maybe Bool
dryRun} -> Maybe Bool
dryRun) (\s :: CancelImageLaunchPermission
s@CancelImageLaunchPermission' {} Maybe Bool
a -> CancelImageLaunchPermission
s {$sel:dryRun:CancelImageLaunchPermission' :: Maybe Bool
dryRun = Maybe Bool
a} :: CancelImageLaunchPermission)

-- | The ID of the AMI that was shared with your Amazon Web Services account.
cancelImageLaunchPermission_imageId :: Lens.Lens' CancelImageLaunchPermission Prelude.Text
cancelImageLaunchPermission_imageId :: Lens' CancelImageLaunchPermission Text
cancelImageLaunchPermission_imageId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CancelImageLaunchPermission' {Text
imageId :: Text
$sel:imageId:CancelImageLaunchPermission' :: CancelImageLaunchPermission -> Text
imageId} -> Text
imageId) (\s :: CancelImageLaunchPermission
s@CancelImageLaunchPermission' {} Text
a -> CancelImageLaunchPermission
s {$sel:imageId:CancelImageLaunchPermission' :: Text
imageId = Text
a} :: CancelImageLaunchPermission)

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

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

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

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

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

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

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