{-# 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.DetachVolume
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Detaches an EBS volume from an instance. Make sure to unmount any file
-- systems on the device within your operating system before detaching the
-- volume. Failure to do so can result in the volume becoming stuck in the
-- @busy@ state while detaching. If this happens, detachment can be delayed
-- indefinitely until you unmount the volume, force detachment, reboot the
-- instance, or all three. If an EBS volume is the root device of an
-- instance, it can\'t be detached while the instance is running. To detach
-- the root volume, stop the instance first.
--
-- When a volume with an Amazon Web Services Marketplace product code is
-- detached from an instance, the product code is no longer associated with
-- the instance.
--
-- For more information, see
-- <https://docs.aws.amazon.com/AWSEC2/latest/UserGuide/ebs-detaching-volume.html Detach an Amazon EBS volume>
-- in the /Amazon Elastic Compute Cloud User Guide/.
module Amazonka.EC2.DetachVolume
  ( -- * Creating a Request
    DetachVolume (..),
    newDetachVolume,

    -- * Request Lenses
    detachVolume_device,
    detachVolume_dryRun,
    detachVolume_force,
    detachVolume_instanceId,
    detachVolume_volumeId,

    -- * Destructuring the Response
    VolumeAttachment (..),
    newVolumeAttachment,

    -- * Response Lenses
    volumeAttachment_attachTime,
    volumeAttachment_deleteOnTermination,
    volumeAttachment_device,
    volumeAttachment_instanceId,
    volumeAttachment_state,
    volumeAttachment_volumeId,
  )
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:/ 'newDetachVolume' smart constructor.
data DetachVolume = DetachVolume'
  { -- | The device name.
    DetachVolume -> Maybe Text
device :: 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@.
    DetachVolume -> Maybe Bool
dryRun :: Prelude.Maybe Prelude.Bool,
    -- | Forces detachment if the previous detachment attempt did not occur
    -- cleanly (for example, logging into an instance, unmounting the volume,
    -- and detaching normally). This option can lead to data loss or a
    -- corrupted file system. Use this option only as a last resort to detach a
    -- volume from a failed instance. The instance won\'t have an opportunity
    -- to flush file system caches or file system metadata. If you use this
    -- option, you must perform file system check and repair procedures.
    DetachVolume -> Maybe Bool
force :: Prelude.Maybe Prelude.Bool,
    -- | The ID of the instance. If you are detaching a Multi-Attach enabled
    -- volume, you must specify an instance ID.
    DetachVolume -> Maybe Text
instanceId :: Prelude.Maybe Prelude.Text,
    -- | The ID of the volume.
    DetachVolume -> Text
volumeId :: Prelude.Text
  }
  deriving (DetachVolume -> DetachVolume -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DetachVolume -> DetachVolume -> Bool
$c/= :: DetachVolume -> DetachVolume -> Bool
== :: DetachVolume -> DetachVolume -> Bool
$c== :: DetachVolume -> DetachVolume -> Bool
Prelude.Eq, ReadPrec [DetachVolume]
ReadPrec DetachVolume
Int -> ReadS DetachVolume
ReadS [DetachVolume]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DetachVolume]
$creadListPrec :: ReadPrec [DetachVolume]
readPrec :: ReadPrec DetachVolume
$creadPrec :: ReadPrec DetachVolume
readList :: ReadS [DetachVolume]
$creadList :: ReadS [DetachVolume]
readsPrec :: Int -> ReadS DetachVolume
$creadsPrec :: Int -> ReadS DetachVolume
Prelude.Read, Int -> DetachVolume -> ShowS
[DetachVolume] -> ShowS
DetachVolume -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DetachVolume] -> ShowS
$cshowList :: [DetachVolume] -> ShowS
show :: DetachVolume -> String
$cshow :: DetachVolume -> String
showsPrec :: Int -> DetachVolume -> ShowS
$cshowsPrec :: Int -> DetachVolume -> ShowS
Prelude.Show, forall x. Rep DetachVolume x -> DetachVolume
forall x. DetachVolume -> Rep DetachVolume x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DetachVolume x -> DetachVolume
$cfrom :: forall x. DetachVolume -> Rep DetachVolume x
Prelude.Generic)

-- |
-- Create a value of 'DetachVolume' 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:
--
-- 'device', 'detachVolume_device' - The device name.
--
-- 'dryRun', 'detachVolume_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@.
--
-- 'force', 'detachVolume_force' - Forces detachment if the previous detachment attempt did not occur
-- cleanly (for example, logging into an instance, unmounting the volume,
-- and detaching normally). This option can lead to data loss or a
-- corrupted file system. Use this option only as a last resort to detach a
-- volume from a failed instance. The instance won\'t have an opportunity
-- to flush file system caches or file system metadata. If you use this
-- option, you must perform file system check and repair procedures.
--
-- 'instanceId', 'detachVolume_instanceId' - The ID of the instance. If you are detaching a Multi-Attach enabled
-- volume, you must specify an instance ID.
--
-- 'volumeId', 'detachVolume_volumeId' - The ID of the volume.
newDetachVolume ::
  -- | 'volumeId'
  Prelude.Text ->
  DetachVolume
newDetachVolume :: Text -> DetachVolume
newDetachVolume Text
pVolumeId_ =
  DetachVolume'
    { $sel:device:DetachVolume' :: Maybe Text
device = forall a. Maybe a
Prelude.Nothing,
      $sel:dryRun:DetachVolume' :: Maybe Bool
dryRun = forall a. Maybe a
Prelude.Nothing,
      $sel:force:DetachVolume' :: Maybe Bool
force = forall a. Maybe a
Prelude.Nothing,
      $sel:instanceId:DetachVolume' :: Maybe Text
instanceId = forall a. Maybe a
Prelude.Nothing,
      $sel:volumeId:DetachVolume' :: Text
volumeId = Text
pVolumeId_
    }

-- | The device name.
detachVolume_device :: Lens.Lens' DetachVolume (Prelude.Maybe Prelude.Text)
detachVolume_device :: Lens' DetachVolume (Maybe Text)
detachVolume_device = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DetachVolume' {Maybe Text
device :: Maybe Text
$sel:device:DetachVolume' :: DetachVolume -> Maybe Text
device} -> Maybe Text
device) (\s :: DetachVolume
s@DetachVolume' {} Maybe Text
a -> DetachVolume
s {$sel:device:DetachVolume' :: Maybe Text
device = Maybe Text
a} :: DetachVolume)

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

-- | Forces detachment if the previous detachment attempt did not occur
-- cleanly (for example, logging into an instance, unmounting the volume,
-- and detaching normally). This option can lead to data loss or a
-- corrupted file system. Use this option only as a last resort to detach a
-- volume from a failed instance. The instance won\'t have an opportunity
-- to flush file system caches or file system metadata. If you use this
-- option, you must perform file system check and repair procedures.
detachVolume_force :: Lens.Lens' DetachVolume (Prelude.Maybe Prelude.Bool)
detachVolume_force :: Lens' DetachVolume (Maybe Bool)
detachVolume_force = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DetachVolume' {Maybe Bool
force :: Maybe Bool
$sel:force:DetachVolume' :: DetachVolume -> Maybe Bool
force} -> Maybe Bool
force) (\s :: DetachVolume
s@DetachVolume' {} Maybe Bool
a -> DetachVolume
s {$sel:force:DetachVolume' :: Maybe Bool
force = Maybe Bool
a} :: DetachVolume)

-- | The ID of the instance. If you are detaching a Multi-Attach enabled
-- volume, you must specify an instance ID.
detachVolume_instanceId :: Lens.Lens' DetachVolume (Prelude.Maybe Prelude.Text)
detachVolume_instanceId :: Lens' DetachVolume (Maybe Text)
detachVolume_instanceId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DetachVolume' {Maybe Text
instanceId :: Maybe Text
$sel:instanceId:DetachVolume' :: DetachVolume -> Maybe Text
instanceId} -> Maybe Text
instanceId) (\s :: DetachVolume
s@DetachVolume' {} Maybe Text
a -> DetachVolume
s {$sel:instanceId:DetachVolume' :: Maybe Text
instanceId = Maybe Text
a} :: DetachVolume)

-- | The ID of the volume.
detachVolume_volumeId :: Lens.Lens' DetachVolume Prelude.Text
detachVolume_volumeId :: Lens' DetachVolume Text
detachVolume_volumeId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DetachVolume' {Text
volumeId :: Text
$sel:volumeId:DetachVolume' :: DetachVolume -> Text
volumeId} -> Text
volumeId) (\s :: DetachVolume
s@DetachVolume' {} Text
a -> DetachVolume
s {$sel:volumeId:DetachVolume' :: Text
volumeId = Text
a} :: DetachVolume)

instance Core.AWSRequest DetachVolume where
  type AWSResponse DetachVolume = VolumeAttachment
  request :: (Service -> Service) -> DetachVolume -> Request DetachVolume
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 DetachVolume
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse DetachVolume)))
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 -> forall a. FromXML a => [Node] -> Either String a
Data.parseXML [Node]
x)

instance Prelude.Hashable DetachVolume where
  hashWithSalt :: Int -> DetachVolume -> Int
hashWithSalt Int
_salt DetachVolume' {Maybe Bool
Maybe Text
Text
volumeId :: Text
instanceId :: Maybe Text
force :: Maybe Bool
dryRun :: Maybe Bool
device :: Maybe Text
$sel:volumeId:DetachVolume' :: DetachVolume -> Text
$sel:instanceId:DetachVolume' :: DetachVolume -> Maybe Text
$sel:force:DetachVolume' :: DetachVolume -> Maybe Bool
$sel:dryRun:DetachVolume' :: DetachVolume -> Maybe Bool
$sel:device:DetachVolume' :: DetachVolume -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
device
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
dryRun
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
force
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
instanceId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
volumeId

instance Prelude.NFData DetachVolume where
  rnf :: DetachVolume -> ()
rnf DetachVolume' {Maybe Bool
Maybe Text
Text
volumeId :: Text
instanceId :: Maybe Text
force :: Maybe Bool
dryRun :: Maybe Bool
device :: Maybe Text
$sel:volumeId:DetachVolume' :: DetachVolume -> Text
$sel:instanceId:DetachVolume' :: DetachVolume -> Maybe Text
$sel:force:DetachVolume' :: DetachVolume -> Maybe Bool
$sel:dryRun:DetachVolume' :: DetachVolume -> Maybe Bool
$sel:device:DetachVolume' :: DetachVolume -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
device
      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 Bool
force
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
instanceId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
volumeId

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

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

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