{-# 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.ResetFpgaImageAttribute
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Resets the specified attribute of the specified Amazon FPGA Image (AFI)
-- to its default value. You can only reset the load permission attribute.
module Amazonka.EC2.ResetFpgaImageAttribute
  ( -- * Creating a Request
    ResetFpgaImageAttribute (..),
    newResetFpgaImageAttribute,

    -- * Request Lenses
    resetFpgaImageAttribute_attribute,
    resetFpgaImageAttribute_dryRun,
    resetFpgaImageAttribute_fpgaImageId,

    -- * Destructuring the Response
    ResetFpgaImageAttributeResponse (..),
    newResetFpgaImageAttributeResponse,

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

-- |
-- Create a value of 'ResetFpgaImageAttribute' 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:
--
-- 'attribute', 'resetFpgaImageAttribute_attribute' - The attribute.
--
-- 'dryRun', 'resetFpgaImageAttribute_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@.
--
-- 'fpgaImageId', 'resetFpgaImageAttribute_fpgaImageId' - The ID of the AFI.
newResetFpgaImageAttribute ::
  -- | 'fpgaImageId'
  Prelude.Text ->
  ResetFpgaImageAttribute
newResetFpgaImageAttribute :: Text -> ResetFpgaImageAttribute
newResetFpgaImageAttribute Text
pFpgaImageId_ =
  ResetFpgaImageAttribute'
    { $sel:attribute:ResetFpgaImageAttribute' :: Maybe ResetFpgaImageAttributeName
attribute =
        forall a. Maybe a
Prelude.Nothing,
      $sel:dryRun:ResetFpgaImageAttribute' :: Maybe Bool
dryRun = forall a. Maybe a
Prelude.Nothing,
      $sel:fpgaImageId:ResetFpgaImageAttribute' :: Text
fpgaImageId = Text
pFpgaImageId_
    }

-- | The attribute.
resetFpgaImageAttribute_attribute :: Lens.Lens' ResetFpgaImageAttribute (Prelude.Maybe ResetFpgaImageAttributeName)
resetFpgaImageAttribute_attribute :: Lens' ResetFpgaImageAttribute (Maybe ResetFpgaImageAttributeName)
resetFpgaImageAttribute_attribute = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ResetFpgaImageAttribute' {Maybe ResetFpgaImageAttributeName
attribute :: Maybe ResetFpgaImageAttributeName
$sel:attribute:ResetFpgaImageAttribute' :: ResetFpgaImageAttribute -> Maybe ResetFpgaImageAttributeName
attribute} -> Maybe ResetFpgaImageAttributeName
attribute) (\s :: ResetFpgaImageAttribute
s@ResetFpgaImageAttribute' {} Maybe ResetFpgaImageAttributeName
a -> ResetFpgaImageAttribute
s {$sel:attribute:ResetFpgaImageAttribute' :: Maybe ResetFpgaImageAttributeName
attribute = Maybe ResetFpgaImageAttributeName
a} :: ResetFpgaImageAttribute)

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

-- | The ID of the AFI.
resetFpgaImageAttribute_fpgaImageId :: Lens.Lens' ResetFpgaImageAttribute Prelude.Text
resetFpgaImageAttribute_fpgaImageId :: Lens' ResetFpgaImageAttribute Text
resetFpgaImageAttribute_fpgaImageId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ResetFpgaImageAttribute' {Text
fpgaImageId :: Text
$sel:fpgaImageId:ResetFpgaImageAttribute' :: ResetFpgaImageAttribute -> Text
fpgaImageId} -> Text
fpgaImageId) (\s :: ResetFpgaImageAttribute
s@ResetFpgaImageAttribute' {} Text
a -> ResetFpgaImageAttribute
s {$sel:fpgaImageId:ResetFpgaImageAttribute' :: Text
fpgaImageId = Text
a} :: ResetFpgaImageAttribute)

instance Core.AWSRequest ResetFpgaImageAttribute where
  type
    AWSResponse ResetFpgaImageAttribute =
      ResetFpgaImageAttributeResponse
  request :: (Service -> Service)
-> ResetFpgaImageAttribute -> Request ResetFpgaImageAttribute
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 ResetFpgaImageAttribute
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse ResetFpgaImageAttribute)))
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 -> ResetFpgaImageAttributeResponse
ResetFpgaImageAttributeResponse'
            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 ResetFpgaImageAttribute where
  hashWithSalt :: Int -> ResetFpgaImageAttribute -> Int
hashWithSalt Int
_salt ResetFpgaImageAttribute' {Maybe Bool
Maybe ResetFpgaImageAttributeName
Text
fpgaImageId :: Text
dryRun :: Maybe Bool
attribute :: Maybe ResetFpgaImageAttributeName
$sel:fpgaImageId:ResetFpgaImageAttribute' :: ResetFpgaImageAttribute -> Text
$sel:dryRun:ResetFpgaImageAttribute' :: ResetFpgaImageAttribute -> Maybe Bool
$sel:attribute:ResetFpgaImageAttribute' :: ResetFpgaImageAttribute -> Maybe ResetFpgaImageAttributeName
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ResetFpgaImageAttributeName
attribute
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
dryRun
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
fpgaImageId

instance Prelude.NFData ResetFpgaImageAttribute where
  rnf :: ResetFpgaImageAttribute -> ()
rnf ResetFpgaImageAttribute' {Maybe Bool
Maybe ResetFpgaImageAttributeName
Text
fpgaImageId :: Text
dryRun :: Maybe Bool
attribute :: Maybe ResetFpgaImageAttributeName
$sel:fpgaImageId:ResetFpgaImageAttribute' :: ResetFpgaImageAttribute -> Text
$sel:dryRun:ResetFpgaImageAttribute' :: ResetFpgaImageAttribute -> Maybe Bool
$sel:attribute:ResetFpgaImageAttribute' :: ResetFpgaImageAttribute -> Maybe ResetFpgaImageAttributeName
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe ResetFpgaImageAttributeName
attribute
      seq :: forall a b. a -> b -> b
`Prelude.seq` 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
fpgaImageId

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

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

instance Data.ToQuery ResetFpgaImageAttribute where
  toQuery :: ResetFpgaImageAttribute -> QueryString
toQuery ResetFpgaImageAttribute' {Maybe Bool
Maybe ResetFpgaImageAttributeName
Text
fpgaImageId :: Text
dryRun :: Maybe Bool
attribute :: Maybe ResetFpgaImageAttributeName
$sel:fpgaImageId:ResetFpgaImageAttribute' :: ResetFpgaImageAttribute -> Text
$sel:dryRun:ResetFpgaImageAttribute' :: ResetFpgaImageAttribute -> Maybe Bool
$sel:attribute:ResetFpgaImageAttribute' :: ResetFpgaImageAttribute -> Maybe ResetFpgaImageAttributeName
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"ResetFpgaImageAttribute" :: Prelude.ByteString),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2016-11-15" :: Prelude.ByteString),
        ByteString
"Attribute" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe ResetFpgaImageAttributeName
attribute,
        ByteString
"DryRun" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Bool
dryRun,
        ByteString
"FpgaImageId" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
fpgaImageId
      ]

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

-- |
-- Create a value of 'ResetFpgaImageAttributeResponse' 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'', 'resetFpgaImageAttributeResponse_return' - Is @true@ if the request succeeds, and an error otherwise.
--
-- 'httpStatus', 'resetFpgaImageAttributeResponse_httpStatus' - The response's http status code.
newResetFpgaImageAttributeResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ResetFpgaImageAttributeResponse
newResetFpgaImageAttributeResponse :: Int -> ResetFpgaImageAttributeResponse
newResetFpgaImageAttributeResponse Int
pHttpStatus_ =
  ResetFpgaImageAttributeResponse'
    { $sel:return':ResetFpgaImageAttributeResponse' :: Maybe Bool
return' =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ResetFpgaImageAttributeResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Is @true@ if the request succeeds, and an error otherwise.
resetFpgaImageAttributeResponse_return :: Lens.Lens' ResetFpgaImageAttributeResponse (Prelude.Maybe Prelude.Bool)
resetFpgaImageAttributeResponse_return :: Lens' ResetFpgaImageAttributeResponse (Maybe Bool)
resetFpgaImageAttributeResponse_return = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ResetFpgaImageAttributeResponse' {Maybe Bool
return' :: Maybe Bool
$sel:return':ResetFpgaImageAttributeResponse' :: ResetFpgaImageAttributeResponse -> Maybe Bool
return'} -> Maybe Bool
return') (\s :: ResetFpgaImageAttributeResponse
s@ResetFpgaImageAttributeResponse' {} Maybe Bool
a -> ResetFpgaImageAttributeResponse
s {$sel:return':ResetFpgaImageAttributeResponse' :: Maybe Bool
return' = Maybe Bool
a} :: ResetFpgaImageAttributeResponse)

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

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