{-# 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.OpsWorks.RegisterVolume
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Registers an Amazon EBS volume with a specified stack. A volume can be
-- registered with only one stack at a time. If the volume is already
-- registered, you must first deregister it by calling DeregisterVolume.
-- For more information, see
-- <https://docs.aws.amazon.com/opsworks/latest/userguide/resources.html Resource Management>.
--
-- __Required Permissions__: To use this action, an IAM user must have a
-- Manage permissions level for the stack, or an attached policy that
-- explicitly grants permissions. For more information on user permissions,
-- see
-- <https://docs.aws.amazon.com/opsworks/latest/userguide/opsworks-security-users.html Managing User Permissions>.
module Amazonka.OpsWorks.RegisterVolume
  ( -- * Creating a Request
    RegisterVolume (..),
    newRegisterVolume,

    -- * Request Lenses
    registerVolume_ec2VolumeId,
    registerVolume_stackId,

    -- * Destructuring the Response
    RegisterVolumeResponse (..),
    newRegisterVolumeResponse,

    -- * Response Lenses
    registerVolumeResponse_volumeId,
    registerVolumeResponse_httpStatus,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.OpsWorks.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newRegisterVolume' smart constructor.
data RegisterVolume = RegisterVolume'
  { -- | The Amazon EBS volume ID.
    RegisterVolume -> Maybe Text
ec2VolumeId :: Prelude.Maybe Prelude.Text,
    -- | The stack ID.
    RegisterVolume -> Text
stackId :: Prelude.Text
  }
  deriving (RegisterVolume -> RegisterVolume -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RegisterVolume -> RegisterVolume -> Bool
$c/= :: RegisterVolume -> RegisterVolume -> Bool
== :: RegisterVolume -> RegisterVolume -> Bool
$c== :: RegisterVolume -> RegisterVolume -> Bool
Prelude.Eq, ReadPrec [RegisterVolume]
ReadPrec RegisterVolume
Int -> ReadS RegisterVolume
ReadS [RegisterVolume]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [RegisterVolume]
$creadListPrec :: ReadPrec [RegisterVolume]
readPrec :: ReadPrec RegisterVolume
$creadPrec :: ReadPrec RegisterVolume
readList :: ReadS [RegisterVolume]
$creadList :: ReadS [RegisterVolume]
readsPrec :: Int -> ReadS RegisterVolume
$creadsPrec :: Int -> ReadS RegisterVolume
Prelude.Read, Int -> RegisterVolume -> ShowS
[RegisterVolume] -> ShowS
RegisterVolume -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RegisterVolume] -> ShowS
$cshowList :: [RegisterVolume] -> ShowS
show :: RegisterVolume -> String
$cshow :: RegisterVolume -> String
showsPrec :: Int -> RegisterVolume -> ShowS
$cshowsPrec :: Int -> RegisterVolume -> ShowS
Prelude.Show, forall x. Rep RegisterVolume x -> RegisterVolume
forall x. RegisterVolume -> Rep RegisterVolume x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RegisterVolume x -> RegisterVolume
$cfrom :: forall x. RegisterVolume -> Rep RegisterVolume x
Prelude.Generic)

-- |
-- Create a value of 'RegisterVolume' 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:
--
-- 'ec2VolumeId', 'registerVolume_ec2VolumeId' - The Amazon EBS volume ID.
--
-- 'stackId', 'registerVolume_stackId' - The stack ID.
newRegisterVolume ::
  -- | 'stackId'
  Prelude.Text ->
  RegisterVolume
newRegisterVolume :: Text -> RegisterVolume
newRegisterVolume Text
pStackId_ =
  RegisterVolume'
    { $sel:ec2VolumeId:RegisterVolume' :: Maybe Text
ec2VolumeId = forall a. Maybe a
Prelude.Nothing,
      $sel:stackId:RegisterVolume' :: Text
stackId = Text
pStackId_
    }

-- | The Amazon EBS volume ID.
registerVolume_ec2VolumeId :: Lens.Lens' RegisterVolume (Prelude.Maybe Prelude.Text)
registerVolume_ec2VolumeId :: Lens' RegisterVolume (Maybe Text)
registerVolume_ec2VolumeId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RegisterVolume' {Maybe Text
ec2VolumeId :: Maybe Text
$sel:ec2VolumeId:RegisterVolume' :: RegisterVolume -> Maybe Text
ec2VolumeId} -> Maybe Text
ec2VolumeId) (\s :: RegisterVolume
s@RegisterVolume' {} Maybe Text
a -> RegisterVolume
s {$sel:ec2VolumeId:RegisterVolume' :: Maybe Text
ec2VolumeId = Maybe Text
a} :: RegisterVolume)

-- | The stack ID.
registerVolume_stackId :: Lens.Lens' RegisterVolume Prelude.Text
registerVolume_stackId :: Lens' RegisterVolume Text
registerVolume_stackId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RegisterVolume' {Text
stackId :: Text
$sel:stackId:RegisterVolume' :: RegisterVolume -> Text
stackId} -> Text
stackId) (\s :: RegisterVolume
s@RegisterVolume' {} Text
a -> RegisterVolume
s {$sel:stackId:RegisterVolume' :: Text
stackId = Text
a} :: RegisterVolume)

instance Core.AWSRequest RegisterVolume where
  type
    AWSResponse RegisterVolume =
      RegisterVolumeResponse
  request :: (Service -> Service) -> RegisterVolume -> Request RegisterVolume
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.postJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy RegisterVolume
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse RegisterVolume)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> Object -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveJSON
      ( \Int
s ResponseHeaders
h Object
x ->
          Maybe Text -> Int -> RegisterVolumeResponse
RegisterVolumeResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"VolumeId")
            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 RegisterVolume where
  hashWithSalt :: Int -> RegisterVolume -> Int
hashWithSalt Int
_salt RegisterVolume' {Maybe Text
Text
stackId :: Text
ec2VolumeId :: Maybe Text
$sel:stackId:RegisterVolume' :: RegisterVolume -> Text
$sel:ec2VolumeId:RegisterVolume' :: RegisterVolume -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
ec2VolumeId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
stackId

instance Prelude.NFData RegisterVolume where
  rnf :: RegisterVolume -> ()
rnf RegisterVolume' {Maybe Text
Text
stackId :: Text
ec2VolumeId :: Maybe Text
$sel:stackId:RegisterVolume' :: RegisterVolume -> Text
$sel:ec2VolumeId:RegisterVolume' :: RegisterVolume -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
ec2VolumeId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
stackId

instance Data.ToHeaders RegisterVolume where
  toHeaders :: RegisterVolume -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"X-Amz-Target"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"OpsWorks_20130218.RegisterVolume" ::
                          Prelude.ByteString
                      ),
            HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON RegisterVolume where
  toJSON :: RegisterVolume -> Value
toJSON RegisterVolume' {Maybe Text
Text
stackId :: Text
ec2VolumeId :: Maybe Text
$sel:stackId:RegisterVolume' :: RegisterVolume -> Text
$sel:ec2VolumeId:RegisterVolume' :: RegisterVolume -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"Ec2VolumeId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
ec2VolumeId,
            forall a. a -> Maybe a
Prelude.Just (Key
"StackId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
stackId)
          ]
      )

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

instance Data.ToQuery RegisterVolume where
  toQuery :: RegisterVolume -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

-- | Contains the response to a @RegisterVolume@ request.
--
-- /See:/ 'newRegisterVolumeResponse' smart constructor.
data RegisterVolumeResponse = RegisterVolumeResponse'
  { -- | The volume ID.
    RegisterVolumeResponse -> Maybe Text
volumeId :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    RegisterVolumeResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (RegisterVolumeResponse -> RegisterVolumeResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RegisterVolumeResponse -> RegisterVolumeResponse -> Bool
$c/= :: RegisterVolumeResponse -> RegisterVolumeResponse -> Bool
== :: RegisterVolumeResponse -> RegisterVolumeResponse -> Bool
$c== :: RegisterVolumeResponse -> RegisterVolumeResponse -> Bool
Prelude.Eq, ReadPrec [RegisterVolumeResponse]
ReadPrec RegisterVolumeResponse
Int -> ReadS RegisterVolumeResponse
ReadS [RegisterVolumeResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [RegisterVolumeResponse]
$creadListPrec :: ReadPrec [RegisterVolumeResponse]
readPrec :: ReadPrec RegisterVolumeResponse
$creadPrec :: ReadPrec RegisterVolumeResponse
readList :: ReadS [RegisterVolumeResponse]
$creadList :: ReadS [RegisterVolumeResponse]
readsPrec :: Int -> ReadS RegisterVolumeResponse
$creadsPrec :: Int -> ReadS RegisterVolumeResponse
Prelude.Read, Int -> RegisterVolumeResponse -> ShowS
[RegisterVolumeResponse] -> ShowS
RegisterVolumeResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RegisterVolumeResponse] -> ShowS
$cshowList :: [RegisterVolumeResponse] -> ShowS
show :: RegisterVolumeResponse -> String
$cshow :: RegisterVolumeResponse -> String
showsPrec :: Int -> RegisterVolumeResponse -> ShowS
$cshowsPrec :: Int -> RegisterVolumeResponse -> ShowS
Prelude.Show, forall x. Rep RegisterVolumeResponse x -> RegisterVolumeResponse
forall x. RegisterVolumeResponse -> Rep RegisterVolumeResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RegisterVolumeResponse x -> RegisterVolumeResponse
$cfrom :: forall x. RegisterVolumeResponse -> Rep RegisterVolumeResponse x
Prelude.Generic)

-- |
-- Create a value of 'RegisterVolumeResponse' 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:
--
-- 'volumeId', 'registerVolumeResponse_volumeId' - The volume ID.
--
-- 'httpStatus', 'registerVolumeResponse_httpStatus' - The response's http status code.
newRegisterVolumeResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  RegisterVolumeResponse
newRegisterVolumeResponse :: Int -> RegisterVolumeResponse
newRegisterVolumeResponse Int
pHttpStatus_ =
  RegisterVolumeResponse'
    { $sel:volumeId:RegisterVolumeResponse' :: Maybe Text
volumeId = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:RegisterVolumeResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

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

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

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