{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# 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.Types.ExportToS3TaskSpecification
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
module Amazonka.EC2.Types.ExportToS3TaskSpecification where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.EC2.Internal
import Amazonka.EC2.Types.ContainerFormat
import Amazonka.EC2.Types.DiskImageFormat
import qualified Amazonka.Prelude as Prelude

-- | Describes an export instance task.
--
-- /See:/ 'newExportToS3TaskSpecification' smart constructor.
data ExportToS3TaskSpecification = ExportToS3TaskSpecification'
  { -- | The container format used to combine disk images with metadata (such as
    -- OVF). If absent, only the disk image is exported.
    ExportToS3TaskSpecification -> Maybe ContainerFormat
containerFormat :: Prelude.Maybe ContainerFormat,
    -- | The format for the exported image.
    ExportToS3TaskSpecification -> Maybe DiskImageFormat
diskImageFormat :: Prelude.Maybe DiskImageFormat,
    -- | The Amazon S3 bucket for the destination image. The destination bucket
    -- must exist and have an access control list (ACL) attached that specifies
    -- the Region-specific canonical account ID for the @Grantee@. For more
    -- information about the ACL to your S3 bucket, see
    -- <https://docs.aws.amazon.com/vm-import/latest/userguide/vmexport.html#vmexport-prerequisites Prerequisites>
    -- in the VM Import\/Export User Guide.
    ExportToS3TaskSpecification -> Maybe Text
s3Bucket :: Prelude.Maybe Prelude.Text,
    -- | The image is written to a single object in the Amazon S3 bucket at the
    -- S3 key s3prefix + exportTaskId + \'.\' + diskImageFormat.
    ExportToS3TaskSpecification -> Maybe Text
s3Prefix :: Prelude.Maybe Prelude.Text
  }
  deriving (ExportToS3TaskSpecification -> ExportToS3TaskSpecification -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ExportToS3TaskSpecification -> ExportToS3TaskSpecification -> Bool
$c/= :: ExportToS3TaskSpecification -> ExportToS3TaskSpecification -> Bool
== :: ExportToS3TaskSpecification -> ExportToS3TaskSpecification -> Bool
$c== :: ExportToS3TaskSpecification -> ExportToS3TaskSpecification -> Bool
Prelude.Eq, ReadPrec [ExportToS3TaskSpecification]
ReadPrec ExportToS3TaskSpecification
Int -> ReadS ExportToS3TaskSpecification
ReadS [ExportToS3TaskSpecification]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ExportToS3TaskSpecification]
$creadListPrec :: ReadPrec [ExportToS3TaskSpecification]
readPrec :: ReadPrec ExportToS3TaskSpecification
$creadPrec :: ReadPrec ExportToS3TaskSpecification
readList :: ReadS [ExportToS3TaskSpecification]
$creadList :: ReadS [ExportToS3TaskSpecification]
readsPrec :: Int -> ReadS ExportToS3TaskSpecification
$creadsPrec :: Int -> ReadS ExportToS3TaskSpecification
Prelude.Read, Int -> ExportToS3TaskSpecification -> ShowS
[ExportToS3TaskSpecification] -> ShowS
ExportToS3TaskSpecification -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ExportToS3TaskSpecification] -> ShowS
$cshowList :: [ExportToS3TaskSpecification] -> ShowS
show :: ExportToS3TaskSpecification -> String
$cshow :: ExportToS3TaskSpecification -> String
showsPrec :: Int -> ExportToS3TaskSpecification -> ShowS
$cshowsPrec :: Int -> ExportToS3TaskSpecification -> ShowS
Prelude.Show, forall x.
Rep ExportToS3TaskSpecification x -> ExportToS3TaskSpecification
forall x.
ExportToS3TaskSpecification -> Rep ExportToS3TaskSpecification x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ExportToS3TaskSpecification x -> ExportToS3TaskSpecification
$cfrom :: forall x.
ExportToS3TaskSpecification -> Rep ExportToS3TaskSpecification x
Prelude.Generic)

-- |
-- Create a value of 'ExportToS3TaskSpecification' 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:
--
-- 'containerFormat', 'exportToS3TaskSpecification_containerFormat' - The container format used to combine disk images with metadata (such as
-- OVF). If absent, only the disk image is exported.
--
-- 'diskImageFormat', 'exportToS3TaskSpecification_diskImageFormat' - The format for the exported image.
--
-- 's3Bucket', 'exportToS3TaskSpecification_s3Bucket' - The Amazon S3 bucket for the destination image. The destination bucket
-- must exist and have an access control list (ACL) attached that specifies
-- the Region-specific canonical account ID for the @Grantee@. For more
-- information about the ACL to your S3 bucket, see
-- <https://docs.aws.amazon.com/vm-import/latest/userguide/vmexport.html#vmexport-prerequisites Prerequisites>
-- in the VM Import\/Export User Guide.
--
-- 's3Prefix', 'exportToS3TaskSpecification_s3Prefix' - The image is written to a single object in the Amazon S3 bucket at the
-- S3 key s3prefix + exportTaskId + \'.\' + diskImageFormat.
newExportToS3TaskSpecification ::
  ExportToS3TaskSpecification
newExportToS3TaskSpecification :: ExportToS3TaskSpecification
newExportToS3TaskSpecification =
  ExportToS3TaskSpecification'
    { $sel:containerFormat:ExportToS3TaskSpecification' :: Maybe ContainerFormat
containerFormat =
        forall a. Maybe a
Prelude.Nothing,
      $sel:diskImageFormat:ExportToS3TaskSpecification' :: Maybe DiskImageFormat
diskImageFormat = forall a. Maybe a
Prelude.Nothing,
      $sel:s3Bucket:ExportToS3TaskSpecification' :: Maybe Text
s3Bucket = forall a. Maybe a
Prelude.Nothing,
      $sel:s3Prefix:ExportToS3TaskSpecification' :: Maybe Text
s3Prefix = forall a. Maybe a
Prelude.Nothing
    }

-- | The container format used to combine disk images with metadata (such as
-- OVF). If absent, only the disk image is exported.
exportToS3TaskSpecification_containerFormat :: Lens.Lens' ExportToS3TaskSpecification (Prelude.Maybe ContainerFormat)
exportToS3TaskSpecification_containerFormat :: Lens' ExportToS3TaskSpecification (Maybe ContainerFormat)
exportToS3TaskSpecification_containerFormat = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ExportToS3TaskSpecification' {Maybe ContainerFormat
containerFormat :: Maybe ContainerFormat
$sel:containerFormat:ExportToS3TaskSpecification' :: ExportToS3TaskSpecification -> Maybe ContainerFormat
containerFormat} -> Maybe ContainerFormat
containerFormat) (\s :: ExportToS3TaskSpecification
s@ExportToS3TaskSpecification' {} Maybe ContainerFormat
a -> ExportToS3TaskSpecification
s {$sel:containerFormat:ExportToS3TaskSpecification' :: Maybe ContainerFormat
containerFormat = Maybe ContainerFormat
a} :: ExportToS3TaskSpecification)

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

-- | The Amazon S3 bucket for the destination image. The destination bucket
-- must exist and have an access control list (ACL) attached that specifies
-- the Region-specific canonical account ID for the @Grantee@. For more
-- information about the ACL to your S3 bucket, see
-- <https://docs.aws.amazon.com/vm-import/latest/userguide/vmexport.html#vmexport-prerequisites Prerequisites>
-- in the VM Import\/Export User Guide.
exportToS3TaskSpecification_s3Bucket :: Lens.Lens' ExportToS3TaskSpecification (Prelude.Maybe Prelude.Text)
exportToS3TaskSpecification_s3Bucket :: Lens' ExportToS3TaskSpecification (Maybe Text)
exportToS3TaskSpecification_s3Bucket = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ExportToS3TaskSpecification' {Maybe Text
s3Bucket :: Maybe Text
$sel:s3Bucket:ExportToS3TaskSpecification' :: ExportToS3TaskSpecification -> Maybe Text
s3Bucket} -> Maybe Text
s3Bucket) (\s :: ExportToS3TaskSpecification
s@ExportToS3TaskSpecification' {} Maybe Text
a -> ExportToS3TaskSpecification
s {$sel:s3Bucket:ExportToS3TaskSpecification' :: Maybe Text
s3Bucket = Maybe Text
a} :: ExportToS3TaskSpecification)

-- | The image is written to a single object in the Amazon S3 bucket at the
-- S3 key s3prefix + exportTaskId + \'.\' + diskImageFormat.
exportToS3TaskSpecification_s3Prefix :: Lens.Lens' ExportToS3TaskSpecification (Prelude.Maybe Prelude.Text)
exportToS3TaskSpecification_s3Prefix :: Lens' ExportToS3TaskSpecification (Maybe Text)
exportToS3TaskSpecification_s3Prefix = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ExportToS3TaskSpecification' {Maybe Text
s3Prefix :: Maybe Text
$sel:s3Prefix:ExportToS3TaskSpecification' :: ExportToS3TaskSpecification -> Maybe Text
s3Prefix} -> Maybe Text
s3Prefix) (\s :: ExportToS3TaskSpecification
s@ExportToS3TaskSpecification' {} Maybe Text
a -> ExportToS3TaskSpecification
s {$sel:s3Prefix:ExportToS3TaskSpecification' :: Maybe Text
s3Prefix = Maybe Text
a} :: ExportToS3TaskSpecification)

instance Prelude.Hashable ExportToS3TaskSpecification where
  hashWithSalt :: Int -> ExportToS3TaskSpecification -> Int
hashWithSalt Int
_salt ExportToS3TaskSpecification' {Maybe Text
Maybe ContainerFormat
Maybe DiskImageFormat
s3Prefix :: Maybe Text
s3Bucket :: Maybe Text
diskImageFormat :: Maybe DiskImageFormat
containerFormat :: Maybe ContainerFormat
$sel:s3Prefix:ExportToS3TaskSpecification' :: ExportToS3TaskSpecification -> Maybe Text
$sel:s3Bucket:ExportToS3TaskSpecification' :: ExportToS3TaskSpecification -> Maybe Text
$sel:diskImageFormat:ExportToS3TaskSpecification' :: ExportToS3TaskSpecification -> Maybe DiskImageFormat
$sel:containerFormat:ExportToS3TaskSpecification' :: ExportToS3TaskSpecification -> Maybe ContainerFormat
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ContainerFormat
containerFormat
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe DiskImageFormat
diskImageFormat
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
s3Bucket
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
s3Prefix

instance Prelude.NFData ExportToS3TaskSpecification where
  rnf :: ExportToS3TaskSpecification -> ()
rnf ExportToS3TaskSpecification' {Maybe Text
Maybe ContainerFormat
Maybe DiskImageFormat
s3Prefix :: Maybe Text
s3Bucket :: Maybe Text
diskImageFormat :: Maybe DiskImageFormat
containerFormat :: Maybe ContainerFormat
$sel:s3Prefix:ExportToS3TaskSpecification' :: ExportToS3TaskSpecification -> Maybe Text
$sel:s3Bucket:ExportToS3TaskSpecification' :: ExportToS3TaskSpecification -> Maybe Text
$sel:diskImageFormat:ExportToS3TaskSpecification' :: ExportToS3TaskSpecification -> Maybe DiskImageFormat
$sel:containerFormat:ExportToS3TaskSpecification' :: ExportToS3TaskSpecification -> Maybe ContainerFormat
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe ContainerFormat
containerFormat
      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
s3Bucket
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
s3Prefix

instance Data.ToQuery ExportToS3TaskSpecification where
  toQuery :: ExportToS3TaskSpecification -> QueryString
toQuery ExportToS3TaskSpecification' {Maybe Text
Maybe ContainerFormat
Maybe DiskImageFormat
s3Prefix :: Maybe Text
s3Bucket :: Maybe Text
diskImageFormat :: Maybe DiskImageFormat
containerFormat :: Maybe ContainerFormat
$sel:s3Prefix:ExportToS3TaskSpecification' :: ExportToS3TaskSpecification -> Maybe Text
$sel:s3Bucket:ExportToS3TaskSpecification' :: ExportToS3TaskSpecification -> Maybe Text
$sel:diskImageFormat:ExportToS3TaskSpecification' :: ExportToS3TaskSpecification -> Maybe DiskImageFormat
$sel:containerFormat:ExportToS3TaskSpecification' :: ExportToS3TaskSpecification -> Maybe ContainerFormat
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"ContainerFormat" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe ContainerFormat
containerFormat,
        ByteString
"DiskImageFormat" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe DiskImageFormat
diskImageFormat,
        ByteString
"S3Bucket" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
s3Bucket,
        ByteString
"S3Prefix" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
s3Prefix
      ]