{-# 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.EnableVolumeIO
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Enables I\/O operations for a volume that had I\/O operations disabled
-- because the data on the volume was potentially inconsistent.
module Amazonka.EC2.EnableVolumeIO
  ( -- * Creating a Request
    EnableVolumeIO (..),
    newEnableVolumeIO,

    -- * Request Lenses
    enableVolumeIO_dryRun,
    enableVolumeIO_volumeId,

    -- * Destructuring the Response
    EnableVolumeIOResponse (..),
    newEnableVolumeIOResponse,
  )
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:/ 'newEnableVolumeIO' smart constructor.
data EnableVolumeIO = EnableVolumeIO'
  { -- | 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@.
    EnableVolumeIO -> Maybe Bool
dryRun :: Prelude.Maybe Prelude.Bool,
    -- | The ID of the volume.
    EnableVolumeIO -> Text
volumeId :: Prelude.Text
  }
  deriving (EnableVolumeIO -> EnableVolumeIO -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EnableVolumeIO -> EnableVolumeIO -> Bool
$c/= :: EnableVolumeIO -> EnableVolumeIO -> Bool
== :: EnableVolumeIO -> EnableVolumeIO -> Bool
$c== :: EnableVolumeIO -> EnableVolumeIO -> Bool
Prelude.Eq, ReadPrec [EnableVolumeIO]
ReadPrec EnableVolumeIO
Int -> ReadS EnableVolumeIO
ReadS [EnableVolumeIO]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [EnableVolumeIO]
$creadListPrec :: ReadPrec [EnableVolumeIO]
readPrec :: ReadPrec EnableVolumeIO
$creadPrec :: ReadPrec EnableVolumeIO
readList :: ReadS [EnableVolumeIO]
$creadList :: ReadS [EnableVolumeIO]
readsPrec :: Int -> ReadS EnableVolumeIO
$creadsPrec :: Int -> ReadS EnableVolumeIO
Prelude.Read, Int -> EnableVolumeIO -> ShowS
[EnableVolumeIO] -> ShowS
EnableVolumeIO -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [EnableVolumeIO] -> ShowS
$cshowList :: [EnableVolumeIO] -> ShowS
show :: EnableVolumeIO -> String
$cshow :: EnableVolumeIO -> String
showsPrec :: Int -> EnableVolumeIO -> ShowS
$cshowsPrec :: Int -> EnableVolumeIO -> ShowS
Prelude.Show, forall x. Rep EnableVolumeIO x -> EnableVolumeIO
forall x. EnableVolumeIO -> Rep EnableVolumeIO x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep EnableVolumeIO x -> EnableVolumeIO
$cfrom :: forall x. EnableVolumeIO -> Rep EnableVolumeIO x
Prelude.Generic)

-- |
-- Create a value of 'EnableVolumeIO' 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', 'enableVolumeIO_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@.
--
-- 'volumeId', 'enableVolumeIO_volumeId' - The ID of the volume.
newEnableVolumeIO ::
  -- | 'volumeId'
  Prelude.Text ->
  EnableVolumeIO
newEnableVolumeIO :: Text -> EnableVolumeIO
newEnableVolumeIO Text
pVolumeId_ =
  EnableVolumeIO'
    { $sel:dryRun:EnableVolumeIO' :: Maybe Bool
dryRun = forall a. Maybe a
Prelude.Nothing,
      $sel:volumeId:EnableVolumeIO' :: Text
volumeId = Text
pVolumeId_
    }

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

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

instance Core.AWSRequest EnableVolumeIO where
  type
    AWSResponse EnableVolumeIO =
      EnableVolumeIOResponse
  request :: (Service -> Service) -> EnableVolumeIO -> Request EnableVolumeIO
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 EnableVolumeIO
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse EnableVolumeIO)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
AWSResponse a
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveNull EnableVolumeIOResponse
EnableVolumeIOResponse'

instance Prelude.Hashable EnableVolumeIO where
  hashWithSalt :: Int -> EnableVolumeIO -> Int
hashWithSalt Int
_salt EnableVolumeIO' {Maybe Bool
Text
volumeId :: Text
dryRun :: Maybe Bool
$sel:volumeId:EnableVolumeIO' :: EnableVolumeIO -> Text
$sel:dryRun:EnableVolumeIO' :: EnableVolumeIO -> 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
volumeId

instance Prelude.NFData EnableVolumeIO where
  rnf :: EnableVolumeIO -> ()
rnf EnableVolumeIO' {Maybe Bool
Text
volumeId :: Text
dryRun :: Maybe Bool
$sel:volumeId:EnableVolumeIO' :: EnableVolumeIO -> Text
$sel:dryRun:EnableVolumeIO' :: EnableVolumeIO -> 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
volumeId

instance Data.ToHeaders EnableVolumeIO where
  toHeaders :: EnableVolumeIO -> [Header]
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

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

instance Data.ToQuery EnableVolumeIO where
  toQuery :: EnableVolumeIO -> QueryString
toQuery EnableVolumeIO' {Maybe Bool
Text
volumeId :: Text
dryRun :: Maybe Bool
$sel:volumeId:EnableVolumeIO' :: EnableVolumeIO -> Text
$sel:dryRun:EnableVolumeIO' :: EnableVolumeIO -> Maybe Bool
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"EnableVolumeIO" :: 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
"VolumeId" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
volumeId
      ]

-- | /See:/ 'newEnableVolumeIOResponse' smart constructor.
data EnableVolumeIOResponse = EnableVolumeIOResponse'
  {
  }
  deriving (EnableVolumeIOResponse -> EnableVolumeIOResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EnableVolumeIOResponse -> EnableVolumeIOResponse -> Bool
$c/= :: EnableVolumeIOResponse -> EnableVolumeIOResponse -> Bool
== :: EnableVolumeIOResponse -> EnableVolumeIOResponse -> Bool
$c== :: EnableVolumeIOResponse -> EnableVolumeIOResponse -> Bool
Prelude.Eq, ReadPrec [EnableVolumeIOResponse]
ReadPrec EnableVolumeIOResponse
Int -> ReadS EnableVolumeIOResponse
ReadS [EnableVolumeIOResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [EnableVolumeIOResponse]
$creadListPrec :: ReadPrec [EnableVolumeIOResponse]
readPrec :: ReadPrec EnableVolumeIOResponse
$creadPrec :: ReadPrec EnableVolumeIOResponse
readList :: ReadS [EnableVolumeIOResponse]
$creadList :: ReadS [EnableVolumeIOResponse]
readsPrec :: Int -> ReadS EnableVolumeIOResponse
$creadsPrec :: Int -> ReadS EnableVolumeIOResponse
Prelude.Read, Int -> EnableVolumeIOResponse -> ShowS
[EnableVolumeIOResponse] -> ShowS
EnableVolumeIOResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [EnableVolumeIOResponse] -> ShowS
$cshowList :: [EnableVolumeIOResponse] -> ShowS
show :: EnableVolumeIOResponse -> String
$cshow :: EnableVolumeIOResponse -> String
showsPrec :: Int -> EnableVolumeIOResponse -> ShowS
$cshowsPrec :: Int -> EnableVolumeIOResponse -> ShowS
Prelude.Show, forall x. Rep EnableVolumeIOResponse x -> EnableVolumeIOResponse
forall x. EnableVolumeIOResponse -> Rep EnableVolumeIOResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep EnableVolumeIOResponse x -> EnableVolumeIOResponse
$cfrom :: forall x. EnableVolumeIOResponse -> Rep EnableVolumeIOResponse x
Prelude.Generic)

-- |
-- Create a value of 'EnableVolumeIOResponse' 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.
newEnableVolumeIOResponse ::
  EnableVolumeIOResponse
newEnableVolumeIOResponse :: EnableVolumeIOResponse
newEnableVolumeIOResponse = EnableVolumeIOResponse
EnableVolumeIOResponse'

instance Prelude.NFData EnableVolumeIOResponse where
  rnf :: EnableVolumeIOResponse -> ()
rnf EnableVolumeIOResponse
_ = ()