{-# 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.BundleInstance
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Bundles an Amazon instance store-backed Windows instance.
--
-- During bundling, only the root device volume (C:\\) is bundled. Data on
-- other instance store volumes is not preserved.
--
-- This action is not applicable for Linux\/Unix instances or Windows
-- instances that are backed by Amazon EBS.
module Amazonka.EC2.BundleInstance
  ( -- * Creating a Request
    BundleInstance (..),
    newBundleInstance,

    -- * Request Lenses
    bundleInstance_dryRun,
    bundleInstance_instanceId,
    bundleInstance_storage,

    -- * Destructuring the Response
    BundleInstanceResponse (..),
    newBundleInstanceResponse,

    -- * Response Lenses
    bundleInstanceResponse_bundleTask,
    bundleInstanceResponse_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

-- | Contains the parameters for BundleInstance.
--
-- /See:/ 'newBundleInstance' smart constructor.
data BundleInstance = BundleInstance'
  { -- | 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@.
    BundleInstance -> Maybe Bool
dryRun :: Prelude.Maybe Prelude.Bool,
    -- | The ID of the instance to bundle.
    --
    -- Type: String
    --
    -- Default: None
    --
    -- Required: Yes
    BundleInstance -> Text
instanceId :: Prelude.Text,
    -- | The bucket in which to store the AMI. You can specify a bucket that you
    -- already own or a new bucket that Amazon EC2 creates on your behalf. If
    -- you specify a bucket that belongs to someone else, Amazon EC2 returns an
    -- error.
    BundleInstance -> Storage
storage :: Storage
  }
  deriving (BundleInstance -> BundleInstance -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BundleInstance -> BundleInstance -> Bool
$c/= :: BundleInstance -> BundleInstance -> Bool
== :: BundleInstance -> BundleInstance -> Bool
$c== :: BundleInstance -> BundleInstance -> Bool
Prelude.Eq, ReadPrec [BundleInstance]
ReadPrec BundleInstance
Int -> ReadS BundleInstance
ReadS [BundleInstance]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [BundleInstance]
$creadListPrec :: ReadPrec [BundleInstance]
readPrec :: ReadPrec BundleInstance
$creadPrec :: ReadPrec BundleInstance
readList :: ReadS [BundleInstance]
$creadList :: ReadS [BundleInstance]
readsPrec :: Int -> ReadS BundleInstance
$creadsPrec :: Int -> ReadS BundleInstance
Prelude.Read, Int -> BundleInstance -> ShowS
[BundleInstance] -> ShowS
BundleInstance -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BundleInstance] -> ShowS
$cshowList :: [BundleInstance] -> ShowS
show :: BundleInstance -> String
$cshow :: BundleInstance -> String
showsPrec :: Int -> BundleInstance -> ShowS
$cshowsPrec :: Int -> BundleInstance -> ShowS
Prelude.Show, forall x. Rep BundleInstance x -> BundleInstance
forall x. BundleInstance -> Rep BundleInstance x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep BundleInstance x -> BundleInstance
$cfrom :: forall x. BundleInstance -> Rep BundleInstance x
Prelude.Generic)

-- |
-- Create a value of 'BundleInstance' with all optional fields omitted.
--
-- Use <https://hackage.haskell.org/package/generic-lens generic-lens> or <https://hackage.haskell.org/package/optics optics> to modify other optional fields.
--
-- The following record fields are available, with the corresponding lenses provided
-- for backwards compatibility:
--
-- 'dryRun', 'bundleInstance_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@.
--
-- 'instanceId', 'bundleInstance_instanceId' - The ID of the instance to bundle.
--
-- Type: String
--
-- Default: None
--
-- Required: Yes
--
-- 'storage', 'bundleInstance_storage' - The bucket in which to store the AMI. You can specify a bucket that you
-- already own or a new bucket that Amazon EC2 creates on your behalf. If
-- you specify a bucket that belongs to someone else, Amazon EC2 returns an
-- error.
newBundleInstance ::
  -- | 'instanceId'
  Prelude.Text ->
  -- | 'storage'
  Storage ->
  BundleInstance
newBundleInstance :: Text -> Storage -> BundleInstance
newBundleInstance Text
pInstanceId_ Storage
pStorage_ =
  BundleInstance'
    { $sel:dryRun:BundleInstance' :: Maybe Bool
dryRun = forall a. Maybe a
Prelude.Nothing,
      $sel:instanceId:BundleInstance' :: Text
instanceId = Text
pInstanceId_,
      $sel:storage:BundleInstance' :: Storage
storage = Storage
pStorage_
    }

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

-- | The ID of the instance to bundle.
--
-- Type: String
--
-- Default: None
--
-- Required: Yes
bundleInstance_instanceId :: Lens.Lens' BundleInstance Prelude.Text
bundleInstance_instanceId :: Lens' BundleInstance Text
bundleInstance_instanceId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BundleInstance' {Text
instanceId :: Text
$sel:instanceId:BundleInstance' :: BundleInstance -> Text
instanceId} -> Text
instanceId) (\s :: BundleInstance
s@BundleInstance' {} Text
a -> BundleInstance
s {$sel:instanceId:BundleInstance' :: Text
instanceId = Text
a} :: BundleInstance)

-- | The bucket in which to store the AMI. You can specify a bucket that you
-- already own or a new bucket that Amazon EC2 creates on your behalf. If
-- you specify a bucket that belongs to someone else, Amazon EC2 returns an
-- error.
bundleInstance_storage :: Lens.Lens' BundleInstance Storage
bundleInstance_storage :: Lens' BundleInstance Storage
bundleInstance_storage = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BundleInstance' {Storage
storage :: Storage
$sel:storage:BundleInstance' :: BundleInstance -> Storage
storage} -> Storage
storage) (\s :: BundleInstance
s@BundleInstance' {} Storage
a -> BundleInstance
s {$sel:storage:BundleInstance' :: Storage
storage = Storage
a} :: BundleInstance)

instance Core.AWSRequest BundleInstance where
  type
    AWSResponse BundleInstance =
      BundleInstanceResponse
  request :: (Service -> Service) -> BundleInstance -> Request BundleInstance
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 BundleInstance
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse BundleInstance)))
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 BundleTask -> Int -> BundleInstanceResponse
BundleInstanceResponse'
            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
"bundleInstanceTask")
            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 BundleInstance where
  hashWithSalt :: Int -> BundleInstance -> Int
hashWithSalt Int
_salt BundleInstance' {Maybe Bool
Text
Storage
storage :: Storage
instanceId :: Text
dryRun :: Maybe Bool
$sel:storage:BundleInstance' :: BundleInstance -> Storage
$sel:instanceId:BundleInstance' :: BundleInstance -> Text
$sel:dryRun:BundleInstance' :: BundleInstance -> Maybe Bool
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
dryRun
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
instanceId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Storage
storage

instance Prelude.NFData BundleInstance where
  rnf :: BundleInstance -> ()
rnf BundleInstance' {Maybe Bool
Text
Storage
storage :: Storage
instanceId :: Text
dryRun :: Maybe Bool
$sel:storage:BundleInstance' :: BundleInstance -> Storage
$sel:instanceId:BundleInstance' :: BundleInstance -> Text
$sel:dryRun:BundleInstance' :: BundleInstance -> Maybe Bool
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
dryRun
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
instanceId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Storage
storage

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

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

instance Data.ToQuery BundleInstance where
  toQuery :: BundleInstance -> QueryString
toQuery BundleInstance' {Maybe Bool
Text
Storage
storage :: Storage
instanceId :: Text
dryRun :: Maybe Bool
$sel:storage:BundleInstance' :: BundleInstance -> Storage
$sel:instanceId:BundleInstance' :: BundleInstance -> Text
$sel:dryRun:BundleInstance' :: BundleInstance -> Maybe Bool
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"BundleInstance" :: Prelude.ByteString),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2016-11-15" :: Prelude.ByteString),
        ByteString
"DryRun" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Bool
dryRun,
        ByteString
"InstanceId" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
instanceId,
        ByteString
"Storage" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Storage
storage
      ]

-- | Contains the output of BundleInstance.
--
-- /See:/ 'newBundleInstanceResponse' smart constructor.
data BundleInstanceResponse = BundleInstanceResponse'
  { -- | Information about the bundle task.
    BundleInstanceResponse -> Maybe BundleTask
bundleTask :: Prelude.Maybe BundleTask,
    -- | The response's http status code.
    BundleInstanceResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (BundleInstanceResponse -> BundleInstanceResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BundleInstanceResponse -> BundleInstanceResponse -> Bool
$c/= :: BundleInstanceResponse -> BundleInstanceResponse -> Bool
== :: BundleInstanceResponse -> BundleInstanceResponse -> Bool
$c== :: BundleInstanceResponse -> BundleInstanceResponse -> Bool
Prelude.Eq, ReadPrec [BundleInstanceResponse]
ReadPrec BundleInstanceResponse
Int -> ReadS BundleInstanceResponse
ReadS [BundleInstanceResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [BundleInstanceResponse]
$creadListPrec :: ReadPrec [BundleInstanceResponse]
readPrec :: ReadPrec BundleInstanceResponse
$creadPrec :: ReadPrec BundleInstanceResponse
readList :: ReadS [BundleInstanceResponse]
$creadList :: ReadS [BundleInstanceResponse]
readsPrec :: Int -> ReadS BundleInstanceResponse
$creadsPrec :: Int -> ReadS BundleInstanceResponse
Prelude.Read, Int -> BundleInstanceResponse -> ShowS
[BundleInstanceResponse] -> ShowS
BundleInstanceResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BundleInstanceResponse] -> ShowS
$cshowList :: [BundleInstanceResponse] -> ShowS
show :: BundleInstanceResponse -> String
$cshow :: BundleInstanceResponse -> String
showsPrec :: Int -> BundleInstanceResponse -> ShowS
$cshowsPrec :: Int -> BundleInstanceResponse -> ShowS
Prelude.Show, forall x. Rep BundleInstanceResponse x -> BundleInstanceResponse
forall x. BundleInstanceResponse -> Rep BundleInstanceResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep BundleInstanceResponse x -> BundleInstanceResponse
$cfrom :: forall x. BundleInstanceResponse -> Rep BundleInstanceResponse x
Prelude.Generic)

-- |
-- Create a value of 'BundleInstanceResponse' 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:
--
-- 'bundleTask', 'bundleInstanceResponse_bundleTask' - Information about the bundle task.
--
-- 'httpStatus', 'bundleInstanceResponse_httpStatus' - The response's http status code.
newBundleInstanceResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  BundleInstanceResponse
newBundleInstanceResponse :: Int -> BundleInstanceResponse
newBundleInstanceResponse Int
pHttpStatus_ =
  BundleInstanceResponse'
    { $sel:bundleTask:BundleInstanceResponse' :: Maybe BundleTask
bundleTask =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:BundleInstanceResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Information about the bundle task.
bundleInstanceResponse_bundleTask :: Lens.Lens' BundleInstanceResponse (Prelude.Maybe BundleTask)
bundleInstanceResponse_bundleTask :: Lens' BundleInstanceResponse (Maybe BundleTask)
bundleInstanceResponse_bundleTask = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BundleInstanceResponse' {Maybe BundleTask
bundleTask :: Maybe BundleTask
$sel:bundleTask:BundleInstanceResponse' :: BundleInstanceResponse -> Maybe BundleTask
bundleTask} -> Maybe BundleTask
bundleTask) (\s :: BundleInstanceResponse
s@BundleInstanceResponse' {} Maybe BundleTask
a -> BundleInstanceResponse
s {$sel:bundleTask:BundleInstanceResponse' :: Maybe BundleTask
bundleTask = Maybe BundleTask
a} :: BundleInstanceResponse)

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

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