{-# 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.AssignInstance
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Assign a registered instance to a layer.
--
-- -   You can assign registered on-premises instances to any layer type.
--
-- -   You can assign registered Amazon EC2 instances only to custom
--     layers.
--
-- -   You cannot use this action with instances that were created with AWS
--     OpsWorks Stacks.
--
-- __Required Permissions__: To use this action, an AWS Identity and Access
-- Management (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.AssignInstance
  ( -- * Creating a Request
    AssignInstance (..),
    newAssignInstance,

    -- * Request Lenses
    assignInstance_instanceId,
    assignInstance_layerIds,

    -- * Destructuring the Response
    AssignInstanceResponse (..),
    newAssignInstanceResponse,
  )
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:/ 'newAssignInstance' smart constructor.
data AssignInstance = AssignInstance'
  { -- | The instance ID.
    AssignInstance -> Text
instanceId :: Prelude.Text,
    -- | The layer ID, which must correspond to a custom layer. You cannot assign
    -- a registered instance to a built-in layer.
    AssignInstance -> [Text]
layerIds :: [Prelude.Text]
  }
  deriving (AssignInstance -> AssignInstance -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AssignInstance -> AssignInstance -> Bool
$c/= :: AssignInstance -> AssignInstance -> Bool
== :: AssignInstance -> AssignInstance -> Bool
$c== :: AssignInstance -> AssignInstance -> Bool
Prelude.Eq, ReadPrec [AssignInstance]
ReadPrec AssignInstance
Int -> ReadS AssignInstance
ReadS [AssignInstance]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AssignInstance]
$creadListPrec :: ReadPrec [AssignInstance]
readPrec :: ReadPrec AssignInstance
$creadPrec :: ReadPrec AssignInstance
readList :: ReadS [AssignInstance]
$creadList :: ReadS [AssignInstance]
readsPrec :: Int -> ReadS AssignInstance
$creadsPrec :: Int -> ReadS AssignInstance
Prelude.Read, Int -> AssignInstance -> ShowS
[AssignInstance] -> ShowS
AssignInstance -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AssignInstance] -> ShowS
$cshowList :: [AssignInstance] -> ShowS
show :: AssignInstance -> String
$cshow :: AssignInstance -> String
showsPrec :: Int -> AssignInstance -> ShowS
$cshowsPrec :: Int -> AssignInstance -> ShowS
Prelude.Show, forall x. Rep AssignInstance x -> AssignInstance
forall x. AssignInstance -> Rep AssignInstance x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AssignInstance x -> AssignInstance
$cfrom :: forall x. AssignInstance -> Rep AssignInstance x
Prelude.Generic)

-- |
-- Create a value of 'AssignInstance' 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:
--
-- 'instanceId', 'assignInstance_instanceId' - The instance ID.
--
-- 'layerIds', 'assignInstance_layerIds' - The layer ID, which must correspond to a custom layer. You cannot assign
-- a registered instance to a built-in layer.
newAssignInstance ::
  -- | 'instanceId'
  Prelude.Text ->
  AssignInstance
newAssignInstance :: Text -> AssignInstance
newAssignInstance Text
pInstanceId_ =
  AssignInstance'
    { $sel:instanceId:AssignInstance' :: Text
instanceId = Text
pInstanceId_,
      $sel:layerIds:AssignInstance' :: [Text]
layerIds = forall a. Monoid a => a
Prelude.mempty
    }

-- | The instance ID.
assignInstance_instanceId :: Lens.Lens' AssignInstance Prelude.Text
assignInstance_instanceId :: Lens' AssignInstance Text
assignInstance_instanceId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AssignInstance' {Text
instanceId :: Text
$sel:instanceId:AssignInstance' :: AssignInstance -> Text
instanceId} -> Text
instanceId) (\s :: AssignInstance
s@AssignInstance' {} Text
a -> AssignInstance
s {$sel:instanceId:AssignInstance' :: Text
instanceId = Text
a} :: AssignInstance)

-- | The layer ID, which must correspond to a custom layer. You cannot assign
-- a registered instance to a built-in layer.
assignInstance_layerIds :: Lens.Lens' AssignInstance [Prelude.Text]
assignInstance_layerIds :: Lens' AssignInstance [Text]
assignInstance_layerIds = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AssignInstance' {[Text]
layerIds :: [Text]
$sel:layerIds:AssignInstance' :: AssignInstance -> [Text]
layerIds} -> [Text]
layerIds) (\s :: AssignInstance
s@AssignInstance' {} [Text]
a -> AssignInstance
s {$sel:layerIds:AssignInstance' :: [Text]
layerIds = [Text]
a} :: AssignInstance) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

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

instance Prelude.Hashable AssignInstance where
  hashWithSalt :: Int -> AssignInstance -> Int
hashWithSalt Int
_salt AssignInstance' {[Text]
Text
layerIds :: [Text]
instanceId :: Text
$sel:layerIds:AssignInstance' :: AssignInstance -> [Text]
$sel:instanceId:AssignInstance' :: AssignInstance -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
instanceId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` [Text]
layerIds

instance Prelude.NFData AssignInstance where
  rnf :: AssignInstance -> ()
rnf AssignInstance' {[Text]
Text
layerIds :: [Text]
instanceId :: Text
$sel:layerIds:AssignInstance' :: AssignInstance -> [Text]
$sel:instanceId:AssignInstance' :: AssignInstance -> Text
..} =
    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 [Text]
layerIds

instance Data.ToHeaders AssignInstance where
  toHeaders :: AssignInstance -> [Header]
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 -> [Header]
Data.=# ( ByteString
"OpsWorks_20130218.AssignInstance" ::
                          Prelude.ByteString
                      ),
            HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> [Header]
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON AssignInstance where
  toJSON :: AssignInstance -> Value
toJSON AssignInstance' {[Text]
Text
layerIds :: [Text]
instanceId :: Text
$sel:layerIds:AssignInstance' :: AssignInstance -> [Text]
$sel:instanceId:AssignInstance' :: AssignInstance -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ forall a. a -> Maybe a
Prelude.Just (Key
"InstanceId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
instanceId),
            forall a. a -> Maybe a
Prelude.Just (Key
"LayerIds" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= [Text]
layerIds)
          ]
      )

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

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

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

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

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