{-# 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.ExportImage
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Exports an Amazon Machine Image (AMI) to a VM file. For more
-- information, see
-- <https://docs.aws.amazon.com/vm-import/latest/userguide/vmexport_image.html Exporting a VM directly from an Amazon Machine Image (AMI)>
-- in the /VM Import\/Export User Guide/.
module Amazonka.EC2.ExportImage
  ( -- * Creating a Request
    ExportImage (..),
    newExportImage,

    -- * Request Lenses
    exportImage_clientToken,
    exportImage_description,
    exportImage_dryRun,
    exportImage_roleName,
    exportImage_tagSpecifications,
    exportImage_diskImageFormat,
    exportImage_imageId,
    exportImage_s3ExportLocation,

    -- * Destructuring the Response
    ExportImageResponse (..),
    newExportImageResponse,

    -- * Response Lenses
    exportImageResponse_description,
    exportImageResponse_diskImageFormat,
    exportImageResponse_exportImageTaskId,
    exportImageResponse_imageId,
    exportImageResponse_progress,
    exportImageResponse_roleName,
    exportImageResponse_s3ExportLocation,
    exportImageResponse_status,
    exportImageResponse_statusMessage,
    exportImageResponse_tags,
    exportImageResponse_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:/ 'newExportImage' smart constructor.
data ExportImage = ExportImage'
  { -- | Token to enable idempotency for export image requests.
    ExportImage -> Maybe Text
clientToken :: Prelude.Maybe Prelude.Text,
    -- | A description of the image being exported. The maximum length is 255
    -- characters.
    ExportImage -> 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@.
    ExportImage -> Maybe Bool
dryRun :: Prelude.Maybe Prelude.Bool,
    -- | The name of the role that grants VM Import\/Export permission to export
    -- images to your Amazon S3 bucket. If this parameter is not specified, the
    -- default role is named \'vmimport\'.
    ExportImage -> Maybe Text
roleName :: Prelude.Maybe Prelude.Text,
    -- | The tags to apply to the export image task during creation.
    ExportImage -> Maybe [TagSpecification]
tagSpecifications :: Prelude.Maybe [TagSpecification],
    -- | The disk image format.
    ExportImage -> DiskImageFormat
diskImageFormat :: DiskImageFormat,
    -- | The ID of the image.
    ExportImage -> Text
imageId :: Prelude.Text,
    -- | The Amazon S3 bucket for the destination image. The destination bucket
    -- must exist.
    ExportImage -> ExportTaskS3LocationRequest
s3ExportLocation :: ExportTaskS3LocationRequest
  }
  deriving (ExportImage -> ExportImage -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ExportImage -> ExportImage -> Bool
$c/= :: ExportImage -> ExportImage -> Bool
== :: ExportImage -> ExportImage -> Bool
$c== :: ExportImage -> ExportImage -> Bool
Prelude.Eq, ReadPrec [ExportImage]
ReadPrec ExportImage
Int -> ReadS ExportImage
ReadS [ExportImage]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ExportImage]
$creadListPrec :: ReadPrec [ExportImage]
readPrec :: ReadPrec ExportImage
$creadPrec :: ReadPrec ExportImage
readList :: ReadS [ExportImage]
$creadList :: ReadS [ExportImage]
readsPrec :: Int -> ReadS ExportImage
$creadsPrec :: Int -> ReadS ExportImage
Prelude.Read, Int -> ExportImage -> ShowS
[ExportImage] -> ShowS
ExportImage -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ExportImage] -> ShowS
$cshowList :: [ExportImage] -> ShowS
show :: ExportImage -> String
$cshow :: ExportImage -> String
showsPrec :: Int -> ExportImage -> ShowS
$cshowsPrec :: Int -> ExportImage -> ShowS
Prelude.Show, forall x. Rep ExportImage x -> ExportImage
forall x. ExportImage -> Rep ExportImage x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ExportImage x -> ExportImage
$cfrom :: forall x. ExportImage -> Rep ExportImage x
Prelude.Generic)

-- |
-- Create a value of 'ExportImage' 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', 'exportImage_clientToken' - Token to enable idempotency for export image requests.
--
-- 'description', 'exportImage_description' - A description of the image being exported. The maximum length is 255
-- characters.
--
-- 'dryRun', 'exportImage_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@.
--
-- 'roleName', 'exportImage_roleName' - The name of the role that grants VM Import\/Export permission to export
-- images to your Amazon S3 bucket. If this parameter is not specified, the
-- default role is named \'vmimport\'.
--
-- 'tagSpecifications', 'exportImage_tagSpecifications' - The tags to apply to the export image task during creation.
--
-- 'diskImageFormat', 'exportImage_diskImageFormat' - The disk image format.
--
-- 'imageId', 'exportImage_imageId' - The ID of the image.
--
-- 's3ExportLocation', 'exportImage_s3ExportLocation' - The Amazon S3 bucket for the destination image. The destination bucket
-- must exist.
newExportImage ::
  -- | 'diskImageFormat'
  DiskImageFormat ->
  -- | 'imageId'
  Prelude.Text ->
  -- | 's3ExportLocation'
  ExportTaskS3LocationRequest ->
  ExportImage
newExportImage :: DiskImageFormat
-> Text -> ExportTaskS3LocationRequest -> ExportImage
newExportImage
  DiskImageFormat
pDiskImageFormat_
  Text
pImageId_
  ExportTaskS3LocationRequest
pS3ExportLocation_ =
    ExportImage'
      { $sel:clientToken:ExportImage' :: Maybe Text
clientToken = forall a. Maybe a
Prelude.Nothing,
        $sel:description:ExportImage' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
        $sel:dryRun:ExportImage' :: Maybe Bool
dryRun = forall a. Maybe a
Prelude.Nothing,
        $sel:roleName:ExportImage' :: Maybe Text
roleName = forall a. Maybe a
Prelude.Nothing,
        $sel:tagSpecifications:ExportImage' :: Maybe [TagSpecification]
tagSpecifications = forall a. Maybe a
Prelude.Nothing,
        $sel:diskImageFormat:ExportImage' :: DiskImageFormat
diskImageFormat = DiskImageFormat
pDiskImageFormat_,
        $sel:imageId:ExportImage' :: Text
imageId = Text
pImageId_,
        $sel:s3ExportLocation:ExportImage' :: ExportTaskS3LocationRequest
s3ExportLocation = ExportTaskS3LocationRequest
pS3ExportLocation_
      }

-- | Token to enable idempotency for export image requests.
exportImage_clientToken :: Lens.Lens' ExportImage (Prelude.Maybe Prelude.Text)
exportImage_clientToken :: Lens' ExportImage (Maybe Text)
exportImage_clientToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ExportImage' {Maybe Text
clientToken :: Maybe Text
$sel:clientToken:ExportImage' :: ExportImage -> Maybe Text
clientToken} -> Maybe Text
clientToken) (\s :: ExportImage
s@ExportImage' {} Maybe Text
a -> ExportImage
s {$sel:clientToken:ExportImage' :: Maybe Text
clientToken = Maybe Text
a} :: ExportImage)

-- | A description of the image being exported. The maximum length is 255
-- characters.
exportImage_description :: Lens.Lens' ExportImage (Prelude.Maybe Prelude.Text)
exportImage_description :: Lens' ExportImage (Maybe Text)
exportImage_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ExportImage' {Maybe Text
description :: Maybe Text
$sel:description:ExportImage' :: ExportImage -> Maybe Text
description} -> Maybe Text
description) (\s :: ExportImage
s@ExportImage' {} Maybe Text
a -> ExportImage
s {$sel:description:ExportImage' :: Maybe Text
description = Maybe Text
a} :: ExportImage)

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

-- | The name of the role that grants VM Import\/Export permission to export
-- images to your Amazon S3 bucket. If this parameter is not specified, the
-- default role is named \'vmimport\'.
exportImage_roleName :: Lens.Lens' ExportImage (Prelude.Maybe Prelude.Text)
exportImage_roleName :: Lens' ExportImage (Maybe Text)
exportImage_roleName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ExportImage' {Maybe Text
roleName :: Maybe Text
$sel:roleName:ExportImage' :: ExportImage -> Maybe Text
roleName} -> Maybe Text
roleName) (\s :: ExportImage
s@ExportImage' {} Maybe Text
a -> ExportImage
s {$sel:roleName:ExportImage' :: Maybe Text
roleName = Maybe Text
a} :: ExportImage)

-- | The tags to apply to the export image task during creation.
exportImage_tagSpecifications :: Lens.Lens' ExportImage (Prelude.Maybe [TagSpecification])
exportImage_tagSpecifications :: Lens' ExportImage (Maybe [TagSpecification])
exportImage_tagSpecifications = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ExportImage' {Maybe [TagSpecification]
tagSpecifications :: Maybe [TagSpecification]
$sel:tagSpecifications:ExportImage' :: ExportImage -> Maybe [TagSpecification]
tagSpecifications} -> Maybe [TagSpecification]
tagSpecifications) (\s :: ExportImage
s@ExportImage' {} Maybe [TagSpecification]
a -> ExportImage
s {$sel:tagSpecifications:ExportImage' :: Maybe [TagSpecification]
tagSpecifications = Maybe [TagSpecification]
a} :: ExportImage) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | The disk image format.
exportImage_diskImageFormat :: Lens.Lens' ExportImage DiskImageFormat
exportImage_diskImageFormat :: Lens' ExportImage DiskImageFormat
exportImage_diskImageFormat = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ExportImage' {DiskImageFormat
diskImageFormat :: DiskImageFormat
$sel:diskImageFormat:ExportImage' :: ExportImage -> DiskImageFormat
diskImageFormat} -> DiskImageFormat
diskImageFormat) (\s :: ExportImage
s@ExportImage' {} DiskImageFormat
a -> ExportImage
s {$sel:diskImageFormat:ExportImage' :: DiskImageFormat
diskImageFormat = DiskImageFormat
a} :: ExportImage)

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

-- | The Amazon S3 bucket for the destination image. The destination bucket
-- must exist.
exportImage_s3ExportLocation :: Lens.Lens' ExportImage ExportTaskS3LocationRequest
exportImage_s3ExportLocation :: Lens' ExportImage ExportTaskS3LocationRequest
exportImage_s3ExportLocation = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ExportImage' {ExportTaskS3LocationRequest
s3ExportLocation :: ExportTaskS3LocationRequest
$sel:s3ExportLocation:ExportImage' :: ExportImage -> ExportTaskS3LocationRequest
s3ExportLocation} -> ExportTaskS3LocationRequest
s3ExportLocation) (\s :: ExportImage
s@ExportImage' {} ExportTaskS3LocationRequest
a -> ExportImage
s {$sel:s3ExportLocation:ExportImage' :: ExportTaskS3LocationRequest
s3ExportLocation = ExportTaskS3LocationRequest
a} :: ExportImage)

instance Core.AWSRequest ExportImage where
  type AWSResponse ExportImage = ExportImageResponse
  request :: (Service -> Service) -> ExportImage -> Request ExportImage
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 ExportImage
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse ExportImage)))
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
-> Maybe DiskImageFormat
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe ExportTaskS3Location
-> Maybe Text
-> Maybe Text
-> Maybe [Tag]
-> Int
-> ExportImageResponse
ExportImageResponse'
            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
"description")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"diskImageFormat")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"exportImageTaskId")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"imageId")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"progress")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"roleName")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"s3ExportLocation")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"status")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"statusMessage")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ( [Node]
x
                            forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"tagSet"
                            forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                            forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
Prelude.>>= forall (f :: * -> *) a b.
Applicative f =>
([a] -> f b) -> [a] -> f (Maybe b)
Core.may (forall a. FromXML a => Text -> [Node] -> Either String [a]
Data.parseXMLList Text
"item")
                        )
            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 ExportImage where
  hashWithSalt :: Int -> ExportImage -> Int
hashWithSalt Int
_salt ExportImage' {Maybe Bool
Maybe [TagSpecification]
Maybe Text
Text
DiskImageFormat
ExportTaskS3LocationRequest
s3ExportLocation :: ExportTaskS3LocationRequest
imageId :: Text
diskImageFormat :: DiskImageFormat
tagSpecifications :: Maybe [TagSpecification]
roleName :: Maybe Text
dryRun :: Maybe Bool
description :: Maybe Text
clientToken :: Maybe Text
$sel:s3ExportLocation:ExportImage' :: ExportImage -> ExportTaskS3LocationRequest
$sel:imageId:ExportImage' :: ExportImage -> Text
$sel:diskImageFormat:ExportImage' :: ExportImage -> DiskImageFormat
$sel:tagSpecifications:ExportImage' :: ExportImage -> Maybe [TagSpecification]
$sel:roleName:ExportImage' :: ExportImage -> Maybe Text
$sel:dryRun:ExportImage' :: ExportImage -> Maybe Bool
$sel:description:ExportImage' :: ExportImage -> Maybe Text
$sel:clientToken:ExportImage' :: ExportImage -> 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
roleName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [TagSpecification]
tagSpecifications
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` DiskImageFormat
diskImageFormat
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
imageId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` ExportTaskS3LocationRequest
s3ExportLocation

instance Prelude.NFData ExportImage where
  rnf :: ExportImage -> ()
rnf ExportImage' {Maybe Bool
Maybe [TagSpecification]
Maybe Text
Text
DiskImageFormat
ExportTaskS3LocationRequest
s3ExportLocation :: ExportTaskS3LocationRequest
imageId :: Text
diskImageFormat :: DiskImageFormat
tagSpecifications :: Maybe [TagSpecification]
roleName :: Maybe Text
dryRun :: Maybe Bool
description :: Maybe Text
clientToken :: Maybe Text
$sel:s3ExportLocation:ExportImage' :: ExportImage -> ExportTaskS3LocationRequest
$sel:imageId:ExportImage' :: ExportImage -> Text
$sel:diskImageFormat:ExportImage' :: ExportImage -> DiskImageFormat
$sel:tagSpecifications:ExportImage' :: ExportImage -> Maybe [TagSpecification]
$sel:roleName:ExportImage' :: ExportImage -> Maybe Text
$sel:dryRun:ExportImage' :: ExportImage -> Maybe Bool
$sel:description:ExportImage' :: ExportImage -> Maybe Text
$sel:clientToken:ExportImage' :: ExportImage -> 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
roleName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [TagSpecification]
tagSpecifications
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf DiskImageFormat
diskImageFormat
      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 ExportTaskS3LocationRequest
s3ExportLocation

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

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

instance Data.ToQuery ExportImage where
  toQuery :: ExportImage -> QueryString
toQuery ExportImage' {Maybe Bool
Maybe [TagSpecification]
Maybe Text
Text
DiskImageFormat
ExportTaskS3LocationRequest
s3ExportLocation :: ExportTaskS3LocationRequest
imageId :: Text
diskImageFormat :: DiskImageFormat
tagSpecifications :: Maybe [TagSpecification]
roleName :: Maybe Text
dryRun :: Maybe Bool
description :: Maybe Text
clientToken :: Maybe Text
$sel:s3ExportLocation:ExportImage' :: ExportImage -> ExportTaskS3LocationRequest
$sel:imageId:ExportImage' :: ExportImage -> Text
$sel:diskImageFormat:ExportImage' :: ExportImage -> DiskImageFormat
$sel:tagSpecifications:ExportImage' :: ExportImage -> Maybe [TagSpecification]
$sel:roleName:ExportImage' :: ExportImage -> Maybe Text
$sel:dryRun:ExportImage' :: ExportImage -> Maybe Bool
$sel:description:ExportImage' :: ExportImage -> Maybe Text
$sel:clientToken:ExportImage' :: ExportImage -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"ExportImage" :: 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
"RoleName" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
roleName,
        forall a. ToQuery a => a -> QueryString
Data.toQuery
          ( forall a.
(IsList a, ToQuery (Item a)) =>
ByteString -> a -> QueryString
Data.toQueryList ByteString
"TagSpecification"
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [TagSpecification]
tagSpecifications
          ),
        ByteString
"DiskImageFormat" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: DiskImageFormat
diskImageFormat,
        ByteString
"ImageId" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
imageId,
        ByteString
"S3ExportLocation" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: ExportTaskS3LocationRequest
s3ExportLocation
      ]

-- | /See:/ 'newExportImageResponse' smart constructor.
data ExportImageResponse = ExportImageResponse'
  { -- | A description of the image being exported.
    ExportImageResponse -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    -- | The disk image format for the exported image.
    ExportImageResponse -> Maybe DiskImageFormat
diskImageFormat :: Prelude.Maybe DiskImageFormat,
    -- | The ID of the export image task.
    ExportImageResponse -> Maybe Text
exportImageTaskId :: Prelude.Maybe Prelude.Text,
    -- | The ID of the image.
    ExportImageResponse -> Maybe Text
imageId :: Prelude.Maybe Prelude.Text,
    -- | The percent complete of the export image task.
    ExportImageResponse -> Maybe Text
progress :: Prelude.Maybe Prelude.Text,
    -- | The name of the role that grants VM Import\/Export permission to export
    -- images to your Amazon S3 bucket.
    ExportImageResponse -> Maybe Text
roleName :: Prelude.Maybe Prelude.Text,
    -- | Information about the destination Amazon S3 bucket.
    ExportImageResponse -> Maybe ExportTaskS3Location
s3ExportLocation :: Prelude.Maybe ExportTaskS3Location,
    -- | The status of the export image task. The possible values are @active@,
    -- @completed@, @deleting@, and @deleted@.
    ExportImageResponse -> Maybe Text
status :: Prelude.Maybe Prelude.Text,
    -- | The status message for the export image task.
    ExportImageResponse -> Maybe Text
statusMessage :: Prelude.Maybe Prelude.Text,
    -- | Any tags assigned to the export image task.
    ExportImageResponse -> Maybe [Tag]
tags :: Prelude.Maybe [Tag],
    -- | The response's http status code.
    ExportImageResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ExportImageResponse -> ExportImageResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ExportImageResponse -> ExportImageResponse -> Bool
$c/= :: ExportImageResponse -> ExportImageResponse -> Bool
== :: ExportImageResponse -> ExportImageResponse -> Bool
$c== :: ExportImageResponse -> ExportImageResponse -> Bool
Prelude.Eq, ReadPrec [ExportImageResponse]
ReadPrec ExportImageResponse
Int -> ReadS ExportImageResponse
ReadS [ExportImageResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ExportImageResponse]
$creadListPrec :: ReadPrec [ExportImageResponse]
readPrec :: ReadPrec ExportImageResponse
$creadPrec :: ReadPrec ExportImageResponse
readList :: ReadS [ExportImageResponse]
$creadList :: ReadS [ExportImageResponse]
readsPrec :: Int -> ReadS ExportImageResponse
$creadsPrec :: Int -> ReadS ExportImageResponse
Prelude.Read, Int -> ExportImageResponse -> ShowS
[ExportImageResponse] -> ShowS
ExportImageResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ExportImageResponse] -> ShowS
$cshowList :: [ExportImageResponse] -> ShowS
show :: ExportImageResponse -> String
$cshow :: ExportImageResponse -> String
showsPrec :: Int -> ExportImageResponse -> ShowS
$cshowsPrec :: Int -> ExportImageResponse -> ShowS
Prelude.Show, forall x. Rep ExportImageResponse x -> ExportImageResponse
forall x. ExportImageResponse -> Rep ExportImageResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ExportImageResponse x -> ExportImageResponse
$cfrom :: forall x. ExportImageResponse -> Rep ExportImageResponse x
Prelude.Generic)

-- |
-- Create a value of 'ExportImageResponse' 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:
--
-- 'description', 'exportImageResponse_description' - A description of the image being exported.
--
-- 'diskImageFormat', 'exportImageResponse_diskImageFormat' - The disk image format for the exported image.
--
-- 'exportImageTaskId', 'exportImageResponse_exportImageTaskId' - The ID of the export image task.
--
-- 'imageId', 'exportImageResponse_imageId' - The ID of the image.
--
-- 'progress', 'exportImageResponse_progress' - The percent complete of the export image task.
--
-- 'roleName', 'exportImageResponse_roleName' - The name of the role that grants VM Import\/Export permission to export
-- images to your Amazon S3 bucket.
--
-- 's3ExportLocation', 'exportImageResponse_s3ExportLocation' - Information about the destination Amazon S3 bucket.
--
-- 'status', 'exportImageResponse_status' - The status of the export image task. The possible values are @active@,
-- @completed@, @deleting@, and @deleted@.
--
-- 'statusMessage', 'exportImageResponse_statusMessage' - The status message for the export image task.
--
-- 'tags', 'exportImageResponse_tags' - Any tags assigned to the export image task.
--
-- 'httpStatus', 'exportImageResponse_httpStatus' - The response's http status code.
newExportImageResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ExportImageResponse
newExportImageResponse :: Int -> ExportImageResponse
newExportImageResponse Int
pHttpStatus_ =
  ExportImageResponse'
    { $sel:description:ExportImageResponse' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
      $sel:diskImageFormat:ExportImageResponse' :: Maybe DiskImageFormat
diskImageFormat = forall a. Maybe a
Prelude.Nothing,
      $sel:exportImageTaskId:ExportImageResponse' :: Maybe Text
exportImageTaskId = forall a. Maybe a
Prelude.Nothing,
      $sel:imageId:ExportImageResponse' :: Maybe Text
imageId = forall a. Maybe a
Prelude.Nothing,
      $sel:progress:ExportImageResponse' :: Maybe Text
progress = forall a. Maybe a
Prelude.Nothing,
      $sel:roleName:ExportImageResponse' :: Maybe Text
roleName = forall a. Maybe a
Prelude.Nothing,
      $sel:s3ExportLocation:ExportImageResponse' :: Maybe ExportTaskS3Location
s3ExportLocation = forall a. Maybe a
Prelude.Nothing,
      $sel:status:ExportImageResponse' :: Maybe Text
status = forall a. Maybe a
Prelude.Nothing,
      $sel:statusMessage:ExportImageResponse' :: Maybe Text
statusMessage = forall a. Maybe a
Prelude.Nothing,
      $sel:tags:ExportImageResponse' :: Maybe [Tag]
tags = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ExportImageResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | A description of the image being exported.
exportImageResponse_description :: Lens.Lens' ExportImageResponse (Prelude.Maybe Prelude.Text)
exportImageResponse_description :: Lens' ExportImageResponse (Maybe Text)
exportImageResponse_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ExportImageResponse' {Maybe Text
description :: Maybe Text
$sel:description:ExportImageResponse' :: ExportImageResponse -> Maybe Text
description} -> Maybe Text
description) (\s :: ExportImageResponse
s@ExportImageResponse' {} Maybe Text
a -> ExportImageResponse
s {$sel:description:ExportImageResponse' :: Maybe Text
description = Maybe Text
a} :: ExportImageResponse)

-- | The disk image format for the exported image.
exportImageResponse_diskImageFormat :: Lens.Lens' ExportImageResponse (Prelude.Maybe DiskImageFormat)
exportImageResponse_diskImageFormat :: Lens' ExportImageResponse (Maybe DiskImageFormat)
exportImageResponse_diskImageFormat = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ExportImageResponse' {Maybe DiskImageFormat
diskImageFormat :: Maybe DiskImageFormat
$sel:diskImageFormat:ExportImageResponse' :: ExportImageResponse -> Maybe DiskImageFormat
diskImageFormat} -> Maybe DiskImageFormat
diskImageFormat) (\s :: ExportImageResponse
s@ExportImageResponse' {} Maybe DiskImageFormat
a -> ExportImageResponse
s {$sel:diskImageFormat:ExportImageResponse' :: Maybe DiskImageFormat
diskImageFormat = Maybe DiskImageFormat
a} :: ExportImageResponse)

-- | The ID of the export image task.
exportImageResponse_exportImageTaskId :: Lens.Lens' ExportImageResponse (Prelude.Maybe Prelude.Text)
exportImageResponse_exportImageTaskId :: Lens' ExportImageResponse (Maybe Text)
exportImageResponse_exportImageTaskId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ExportImageResponse' {Maybe Text
exportImageTaskId :: Maybe Text
$sel:exportImageTaskId:ExportImageResponse' :: ExportImageResponse -> Maybe Text
exportImageTaskId} -> Maybe Text
exportImageTaskId) (\s :: ExportImageResponse
s@ExportImageResponse' {} Maybe Text
a -> ExportImageResponse
s {$sel:exportImageTaskId:ExportImageResponse' :: Maybe Text
exportImageTaskId = Maybe Text
a} :: ExportImageResponse)

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

-- | The percent complete of the export image task.
exportImageResponse_progress :: Lens.Lens' ExportImageResponse (Prelude.Maybe Prelude.Text)
exportImageResponse_progress :: Lens' ExportImageResponse (Maybe Text)
exportImageResponse_progress = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ExportImageResponse' {Maybe Text
progress :: Maybe Text
$sel:progress:ExportImageResponse' :: ExportImageResponse -> Maybe Text
progress} -> Maybe Text
progress) (\s :: ExportImageResponse
s@ExportImageResponse' {} Maybe Text
a -> ExportImageResponse
s {$sel:progress:ExportImageResponse' :: Maybe Text
progress = Maybe Text
a} :: ExportImageResponse)

-- | The name of the role that grants VM Import\/Export permission to export
-- images to your Amazon S3 bucket.
exportImageResponse_roleName :: Lens.Lens' ExportImageResponse (Prelude.Maybe Prelude.Text)
exportImageResponse_roleName :: Lens' ExportImageResponse (Maybe Text)
exportImageResponse_roleName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ExportImageResponse' {Maybe Text
roleName :: Maybe Text
$sel:roleName:ExportImageResponse' :: ExportImageResponse -> Maybe Text
roleName} -> Maybe Text
roleName) (\s :: ExportImageResponse
s@ExportImageResponse' {} Maybe Text
a -> ExportImageResponse
s {$sel:roleName:ExportImageResponse' :: Maybe Text
roleName = Maybe Text
a} :: ExportImageResponse)

-- | Information about the destination Amazon S3 bucket.
exportImageResponse_s3ExportLocation :: Lens.Lens' ExportImageResponse (Prelude.Maybe ExportTaskS3Location)
exportImageResponse_s3ExportLocation :: Lens' ExportImageResponse (Maybe ExportTaskS3Location)
exportImageResponse_s3ExportLocation = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ExportImageResponse' {Maybe ExportTaskS3Location
s3ExportLocation :: Maybe ExportTaskS3Location
$sel:s3ExportLocation:ExportImageResponse' :: ExportImageResponse -> Maybe ExportTaskS3Location
s3ExportLocation} -> Maybe ExportTaskS3Location
s3ExportLocation) (\s :: ExportImageResponse
s@ExportImageResponse' {} Maybe ExportTaskS3Location
a -> ExportImageResponse
s {$sel:s3ExportLocation:ExportImageResponse' :: Maybe ExportTaskS3Location
s3ExportLocation = Maybe ExportTaskS3Location
a} :: ExportImageResponse)

-- | The status of the export image task. The possible values are @active@,
-- @completed@, @deleting@, and @deleted@.
exportImageResponse_status :: Lens.Lens' ExportImageResponse (Prelude.Maybe Prelude.Text)
exportImageResponse_status :: Lens' ExportImageResponse (Maybe Text)
exportImageResponse_status = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ExportImageResponse' {Maybe Text
status :: Maybe Text
$sel:status:ExportImageResponse' :: ExportImageResponse -> Maybe Text
status} -> Maybe Text
status) (\s :: ExportImageResponse
s@ExportImageResponse' {} Maybe Text
a -> ExportImageResponse
s {$sel:status:ExportImageResponse' :: Maybe Text
status = Maybe Text
a} :: ExportImageResponse)

-- | The status message for the export image task.
exportImageResponse_statusMessage :: Lens.Lens' ExportImageResponse (Prelude.Maybe Prelude.Text)
exportImageResponse_statusMessage :: Lens' ExportImageResponse (Maybe Text)
exportImageResponse_statusMessage = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ExportImageResponse' {Maybe Text
statusMessage :: Maybe Text
$sel:statusMessage:ExportImageResponse' :: ExportImageResponse -> Maybe Text
statusMessage} -> Maybe Text
statusMessage) (\s :: ExportImageResponse
s@ExportImageResponse' {} Maybe Text
a -> ExportImageResponse
s {$sel:statusMessage:ExportImageResponse' :: Maybe Text
statusMessage = Maybe Text
a} :: ExportImageResponse)

-- | Any tags assigned to the export image task.
exportImageResponse_tags :: Lens.Lens' ExportImageResponse (Prelude.Maybe [Tag])
exportImageResponse_tags :: Lens' ExportImageResponse (Maybe [Tag])
exportImageResponse_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ExportImageResponse' {Maybe [Tag]
tags :: Maybe [Tag]
$sel:tags:ExportImageResponse' :: ExportImageResponse -> Maybe [Tag]
tags} -> Maybe [Tag]
tags) (\s :: ExportImageResponse
s@ExportImageResponse' {} Maybe [Tag]
a -> ExportImageResponse
s {$sel:tags:ExportImageResponse' :: Maybe [Tag]
tags = Maybe [Tag]
a} :: ExportImageResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

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

instance Prelude.NFData ExportImageResponse where
  rnf :: ExportImageResponse -> ()
rnf ExportImageResponse' {Int
Maybe [Tag]
Maybe Text
Maybe DiskImageFormat
Maybe ExportTaskS3Location
httpStatus :: Int
tags :: Maybe [Tag]
statusMessage :: Maybe Text
status :: Maybe Text
s3ExportLocation :: Maybe ExportTaskS3Location
roleName :: Maybe Text
progress :: Maybe Text
imageId :: Maybe Text
exportImageTaskId :: Maybe Text
diskImageFormat :: Maybe DiskImageFormat
description :: Maybe Text
$sel:httpStatus:ExportImageResponse' :: ExportImageResponse -> Int
$sel:tags:ExportImageResponse' :: ExportImageResponse -> Maybe [Tag]
$sel:statusMessage:ExportImageResponse' :: ExportImageResponse -> Maybe Text
$sel:status:ExportImageResponse' :: ExportImageResponse -> Maybe Text
$sel:s3ExportLocation:ExportImageResponse' :: ExportImageResponse -> Maybe ExportTaskS3Location
$sel:roleName:ExportImageResponse' :: ExportImageResponse -> Maybe Text
$sel:progress:ExportImageResponse' :: ExportImageResponse -> Maybe Text
$sel:imageId:ExportImageResponse' :: ExportImageResponse -> Maybe Text
$sel:exportImageTaskId:ExportImageResponse' :: ExportImageResponse -> Maybe Text
$sel:diskImageFormat:ExportImageResponse' :: ExportImageResponse -> Maybe DiskImageFormat
$sel:description:ExportImageResponse' :: ExportImageResponse -> Maybe Text
..} =
    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 DiskImageFormat
diskImageFormat
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
exportImageTaskId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
imageId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
progress
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
roleName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ExportTaskS3Location
s3ExportLocation
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
status
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
statusMessage
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Tag]
tags
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus