{-# 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.CopyFpgaImage
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Copies the specified Amazon FPGA Image (AFI) to the current Region.
module Amazonka.EC2.CopyFpgaImage
  ( -- * Creating a Request
    CopyFpgaImage (..),
    newCopyFpgaImage,

    -- * Request Lenses
    copyFpgaImage_clientToken,
    copyFpgaImage_description,
    copyFpgaImage_dryRun,
    copyFpgaImage_name,
    copyFpgaImage_sourceFpgaImageId,
    copyFpgaImage_sourceRegion,

    -- * Destructuring the Response
    CopyFpgaImageResponse (..),
    newCopyFpgaImageResponse,

    -- * Response Lenses
    copyFpgaImageResponse_fpgaImageId,
    copyFpgaImageResponse_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:/ 'newCopyFpgaImage' smart constructor.
data CopyFpgaImage = CopyFpgaImage'
  { -- | Unique, case-sensitive identifier that you provide to ensure the
    -- idempotency of the request. For more information, see
    -- <https://docs.aws.amazon.com/AWSEC2/latest/UserGuide/Run_Instance_Idempotency.html Ensuring idempotency>.
    CopyFpgaImage -> Maybe Text
clientToken :: Prelude.Maybe Prelude.Text,
    -- | The description for the new AFI.
    CopyFpgaImage -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    -- | 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@.
    CopyFpgaImage -> Maybe Bool
dryRun :: Prelude.Maybe Prelude.Bool,
    -- | The name for the new AFI. The default is the name of the source AFI.
    CopyFpgaImage -> Maybe Text
name :: Prelude.Maybe Prelude.Text,
    -- | The ID of the source AFI.
    CopyFpgaImage -> Text
sourceFpgaImageId :: Prelude.Text,
    -- | The Region that contains the source AFI.
    CopyFpgaImage -> Text
sourceRegion :: Prelude.Text
  }
  deriving (CopyFpgaImage -> CopyFpgaImage -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CopyFpgaImage -> CopyFpgaImage -> Bool
$c/= :: CopyFpgaImage -> CopyFpgaImage -> Bool
== :: CopyFpgaImage -> CopyFpgaImage -> Bool
$c== :: CopyFpgaImage -> CopyFpgaImage -> Bool
Prelude.Eq, ReadPrec [CopyFpgaImage]
ReadPrec CopyFpgaImage
Int -> ReadS CopyFpgaImage
ReadS [CopyFpgaImage]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CopyFpgaImage]
$creadListPrec :: ReadPrec [CopyFpgaImage]
readPrec :: ReadPrec CopyFpgaImage
$creadPrec :: ReadPrec CopyFpgaImage
readList :: ReadS [CopyFpgaImage]
$creadList :: ReadS [CopyFpgaImage]
readsPrec :: Int -> ReadS CopyFpgaImage
$creadsPrec :: Int -> ReadS CopyFpgaImage
Prelude.Read, Int -> CopyFpgaImage -> ShowS
[CopyFpgaImage] -> ShowS
CopyFpgaImage -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CopyFpgaImage] -> ShowS
$cshowList :: [CopyFpgaImage] -> ShowS
show :: CopyFpgaImage -> String
$cshow :: CopyFpgaImage -> String
showsPrec :: Int -> CopyFpgaImage -> ShowS
$cshowsPrec :: Int -> CopyFpgaImage -> ShowS
Prelude.Show, forall x. Rep CopyFpgaImage x -> CopyFpgaImage
forall x. CopyFpgaImage -> Rep CopyFpgaImage x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CopyFpgaImage x -> CopyFpgaImage
$cfrom :: forall x. CopyFpgaImage -> Rep CopyFpgaImage x
Prelude.Generic)

-- |
-- Create a value of 'CopyFpgaImage' 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:
--
-- 'clientToken', 'copyFpgaImage_clientToken' - Unique, case-sensitive identifier that you provide to ensure the
-- idempotency of the request. For more information, see
-- <https://docs.aws.amazon.com/AWSEC2/latest/UserGuide/Run_Instance_Idempotency.html Ensuring idempotency>.
--
-- 'description', 'copyFpgaImage_description' - The description for the new AFI.
--
-- 'dryRun', 'copyFpgaImage_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@.
--
-- 'name', 'copyFpgaImage_name' - The name for the new AFI. The default is the name of the source AFI.
--
-- 'sourceFpgaImageId', 'copyFpgaImage_sourceFpgaImageId' - The ID of the source AFI.
--
-- 'sourceRegion', 'copyFpgaImage_sourceRegion' - The Region that contains the source AFI.
newCopyFpgaImage ::
  -- | 'sourceFpgaImageId'
  Prelude.Text ->
  -- | 'sourceRegion'
  Prelude.Text ->
  CopyFpgaImage
newCopyFpgaImage :: Text -> Text -> CopyFpgaImage
newCopyFpgaImage Text
pSourceFpgaImageId_ Text
pSourceRegion_ =
  CopyFpgaImage'
    { $sel:clientToken:CopyFpgaImage' :: Maybe Text
clientToken = forall a. Maybe a
Prelude.Nothing,
      $sel:description:CopyFpgaImage' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
      $sel:dryRun:CopyFpgaImage' :: Maybe Bool
dryRun = forall a. Maybe a
Prelude.Nothing,
      $sel:name:CopyFpgaImage' :: Maybe Text
name = forall a. Maybe a
Prelude.Nothing,
      $sel:sourceFpgaImageId:CopyFpgaImage' :: Text
sourceFpgaImageId = Text
pSourceFpgaImageId_,
      $sel:sourceRegion:CopyFpgaImage' :: Text
sourceRegion = Text
pSourceRegion_
    }

-- | Unique, case-sensitive identifier that you provide to ensure the
-- idempotency of the request. For more information, see
-- <https://docs.aws.amazon.com/AWSEC2/latest/UserGuide/Run_Instance_Idempotency.html Ensuring idempotency>.
copyFpgaImage_clientToken :: Lens.Lens' CopyFpgaImage (Prelude.Maybe Prelude.Text)
copyFpgaImage_clientToken :: Lens' CopyFpgaImage (Maybe Text)
copyFpgaImage_clientToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CopyFpgaImage' {Maybe Text
clientToken :: Maybe Text
$sel:clientToken:CopyFpgaImage' :: CopyFpgaImage -> Maybe Text
clientToken} -> Maybe Text
clientToken) (\s :: CopyFpgaImage
s@CopyFpgaImage' {} Maybe Text
a -> CopyFpgaImage
s {$sel:clientToken:CopyFpgaImage' :: Maybe Text
clientToken = Maybe Text
a} :: CopyFpgaImage)

-- | The description for the new AFI.
copyFpgaImage_description :: Lens.Lens' CopyFpgaImage (Prelude.Maybe Prelude.Text)
copyFpgaImage_description :: Lens' CopyFpgaImage (Maybe Text)
copyFpgaImage_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CopyFpgaImage' {Maybe Text
description :: Maybe Text
$sel:description:CopyFpgaImage' :: CopyFpgaImage -> Maybe Text
description} -> Maybe Text
description) (\s :: CopyFpgaImage
s@CopyFpgaImage' {} Maybe Text
a -> CopyFpgaImage
s {$sel:description:CopyFpgaImage' :: Maybe Text
description = Maybe Text
a} :: CopyFpgaImage)

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

-- | The name for the new AFI. The default is the name of the source AFI.
copyFpgaImage_name :: Lens.Lens' CopyFpgaImage (Prelude.Maybe Prelude.Text)
copyFpgaImage_name :: Lens' CopyFpgaImage (Maybe Text)
copyFpgaImage_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CopyFpgaImage' {Maybe Text
name :: Maybe Text
$sel:name:CopyFpgaImage' :: CopyFpgaImage -> Maybe Text
name} -> Maybe Text
name) (\s :: CopyFpgaImage
s@CopyFpgaImage' {} Maybe Text
a -> CopyFpgaImage
s {$sel:name:CopyFpgaImage' :: Maybe Text
name = Maybe Text
a} :: CopyFpgaImage)

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

-- | The Region that contains the source AFI.
copyFpgaImage_sourceRegion :: Lens.Lens' CopyFpgaImage Prelude.Text
copyFpgaImage_sourceRegion :: Lens' CopyFpgaImage Text
copyFpgaImage_sourceRegion = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CopyFpgaImage' {Text
sourceRegion :: Text
$sel:sourceRegion:CopyFpgaImage' :: CopyFpgaImage -> Text
sourceRegion} -> Text
sourceRegion) (\s :: CopyFpgaImage
s@CopyFpgaImage' {} Text
a -> CopyFpgaImage
s {$sel:sourceRegion:CopyFpgaImage' :: Text
sourceRegion = Text
a} :: CopyFpgaImage)

instance Core.AWSRequest CopyFpgaImage where
  type
    AWSResponse CopyFpgaImage =
      CopyFpgaImageResponse
  request :: (Service -> Service) -> CopyFpgaImage -> Request CopyFpgaImage
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 CopyFpgaImage
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse CopyFpgaImage)))
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 Text -> Int -> CopyFpgaImageResponse
CopyFpgaImageResponse'
            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
"fpgaImageId")
            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 CopyFpgaImage where
  hashWithSalt :: Int -> CopyFpgaImage -> Int
hashWithSalt Int
_salt CopyFpgaImage' {Maybe Bool
Maybe Text
Text
sourceRegion :: Text
sourceFpgaImageId :: Text
name :: Maybe Text
dryRun :: Maybe Bool
description :: Maybe Text
clientToken :: Maybe Text
$sel:sourceRegion:CopyFpgaImage' :: CopyFpgaImage -> Text
$sel:sourceFpgaImageId:CopyFpgaImage' :: CopyFpgaImage -> Text
$sel:name:CopyFpgaImage' :: CopyFpgaImage -> Maybe Text
$sel:dryRun:CopyFpgaImage' :: CopyFpgaImage -> Maybe Bool
$sel:description:CopyFpgaImage' :: CopyFpgaImage -> Maybe Text
$sel:clientToken:CopyFpgaImage' :: CopyFpgaImage -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
clientToken
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
description
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
dryRun
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
name
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
sourceFpgaImageId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
sourceRegion

instance Prelude.NFData CopyFpgaImage where
  rnf :: CopyFpgaImage -> ()
rnf CopyFpgaImage' {Maybe Bool
Maybe Text
Text
sourceRegion :: Text
sourceFpgaImageId :: Text
name :: Maybe Text
dryRun :: Maybe Bool
description :: Maybe Text
clientToken :: Maybe Text
$sel:sourceRegion:CopyFpgaImage' :: CopyFpgaImage -> Text
$sel:sourceFpgaImageId:CopyFpgaImage' :: CopyFpgaImage -> Text
$sel:name:CopyFpgaImage' :: CopyFpgaImage -> Maybe Text
$sel:dryRun:CopyFpgaImage' :: CopyFpgaImage -> Maybe Bool
$sel:description:CopyFpgaImage' :: CopyFpgaImage -> Maybe Text
$sel:clientToken:CopyFpgaImage' :: CopyFpgaImage -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
clientToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
description
      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 Maybe Text
name
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
sourceFpgaImageId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
sourceRegion

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

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

instance Data.ToQuery CopyFpgaImage where
  toQuery :: CopyFpgaImage -> QueryString
toQuery CopyFpgaImage' {Maybe Bool
Maybe Text
Text
sourceRegion :: Text
sourceFpgaImageId :: Text
name :: Maybe Text
dryRun :: Maybe Bool
description :: Maybe Text
clientToken :: Maybe Text
$sel:sourceRegion:CopyFpgaImage' :: CopyFpgaImage -> Text
$sel:sourceFpgaImageId:CopyFpgaImage' :: CopyFpgaImage -> Text
$sel:name:CopyFpgaImage' :: CopyFpgaImage -> Maybe Text
$sel:dryRun:CopyFpgaImage' :: CopyFpgaImage -> Maybe Bool
$sel:description:CopyFpgaImage' :: CopyFpgaImage -> Maybe Text
$sel:clientToken:CopyFpgaImage' :: CopyFpgaImage -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"CopyFpgaImage" :: Prelude.ByteString),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2016-11-15" :: Prelude.ByteString),
        ByteString
"ClientToken" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
clientToken,
        ByteString
"Description" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
description,
        ByteString
"DryRun" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Bool
dryRun,
        ByteString
"Name" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
name,
        ByteString
"SourceFpgaImageId" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
sourceFpgaImageId,
        ByteString
"SourceRegion" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
sourceRegion
      ]

-- | /See:/ 'newCopyFpgaImageResponse' smart constructor.
data CopyFpgaImageResponse = CopyFpgaImageResponse'
  { -- | The ID of the new AFI.
    CopyFpgaImageResponse -> Maybe Text
fpgaImageId :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    CopyFpgaImageResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (CopyFpgaImageResponse -> CopyFpgaImageResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CopyFpgaImageResponse -> CopyFpgaImageResponse -> Bool
$c/= :: CopyFpgaImageResponse -> CopyFpgaImageResponse -> Bool
== :: CopyFpgaImageResponse -> CopyFpgaImageResponse -> Bool
$c== :: CopyFpgaImageResponse -> CopyFpgaImageResponse -> Bool
Prelude.Eq, ReadPrec [CopyFpgaImageResponse]
ReadPrec CopyFpgaImageResponse
Int -> ReadS CopyFpgaImageResponse
ReadS [CopyFpgaImageResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CopyFpgaImageResponse]
$creadListPrec :: ReadPrec [CopyFpgaImageResponse]
readPrec :: ReadPrec CopyFpgaImageResponse
$creadPrec :: ReadPrec CopyFpgaImageResponse
readList :: ReadS [CopyFpgaImageResponse]
$creadList :: ReadS [CopyFpgaImageResponse]
readsPrec :: Int -> ReadS CopyFpgaImageResponse
$creadsPrec :: Int -> ReadS CopyFpgaImageResponse
Prelude.Read, Int -> CopyFpgaImageResponse -> ShowS
[CopyFpgaImageResponse] -> ShowS
CopyFpgaImageResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CopyFpgaImageResponse] -> ShowS
$cshowList :: [CopyFpgaImageResponse] -> ShowS
show :: CopyFpgaImageResponse -> String
$cshow :: CopyFpgaImageResponse -> String
showsPrec :: Int -> CopyFpgaImageResponse -> ShowS
$cshowsPrec :: Int -> CopyFpgaImageResponse -> ShowS
Prelude.Show, forall x. Rep CopyFpgaImageResponse x -> CopyFpgaImageResponse
forall x. CopyFpgaImageResponse -> Rep CopyFpgaImageResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CopyFpgaImageResponse x -> CopyFpgaImageResponse
$cfrom :: forall x. CopyFpgaImageResponse -> Rep CopyFpgaImageResponse x
Prelude.Generic)

-- |
-- Create a value of 'CopyFpgaImageResponse' 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:
--
-- 'fpgaImageId', 'copyFpgaImageResponse_fpgaImageId' - The ID of the new AFI.
--
-- 'httpStatus', 'copyFpgaImageResponse_httpStatus' - The response's http status code.
newCopyFpgaImageResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  CopyFpgaImageResponse
newCopyFpgaImageResponse :: Int -> CopyFpgaImageResponse
newCopyFpgaImageResponse Int
pHttpStatus_ =
  CopyFpgaImageResponse'
    { $sel:fpgaImageId:CopyFpgaImageResponse' :: Maybe Text
fpgaImageId =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:CopyFpgaImageResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

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

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

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