{-# 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.MGN.AssociateApplications
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Associate applications to wave.
module Amazonka.MGN.AssociateApplications
  ( -- * Creating a Request
    AssociateApplications (..),
    newAssociateApplications,

    -- * Request Lenses
    associateApplications_applicationIDs,
    associateApplications_waveID,

    -- * Destructuring the Response
    AssociateApplicationsResponse (..),
    newAssociateApplicationsResponse,

    -- * Response Lenses
    associateApplicationsResponse_httpStatus,
  )
where

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

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

-- |
-- Create a value of 'AssociateApplications' 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:
--
-- 'applicationIDs', 'associateApplications_applicationIDs' - Application IDs list.
--
-- 'waveID', 'associateApplications_waveID' - Wave ID.
newAssociateApplications ::
  -- | 'applicationIDs'
  Prelude.NonEmpty Prelude.Text ->
  -- | 'waveID'
  Prelude.Text ->
  AssociateApplications
newAssociateApplications :: NonEmpty Text -> Text -> AssociateApplications
newAssociateApplications NonEmpty Text
pApplicationIDs_ Text
pWaveID_ =
  AssociateApplications'
    { $sel:applicationIDs:AssociateApplications' :: NonEmpty Text
applicationIDs =
        forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced forall t b. AReview t b -> b -> t
Lens.# NonEmpty Text
pApplicationIDs_,
      $sel:waveID:AssociateApplications' :: Text
waveID = Text
pWaveID_
    }

-- | Application IDs list.
associateApplications_applicationIDs :: Lens.Lens' AssociateApplications (Prelude.NonEmpty Prelude.Text)
associateApplications_applicationIDs :: Lens' AssociateApplications (NonEmpty Text)
associateApplications_applicationIDs = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AssociateApplications' {NonEmpty Text
applicationIDs :: NonEmpty Text
$sel:applicationIDs:AssociateApplications' :: AssociateApplications -> NonEmpty Text
applicationIDs} -> NonEmpty Text
applicationIDs) (\s :: AssociateApplications
s@AssociateApplications' {} NonEmpty Text
a -> AssociateApplications
s {$sel:applicationIDs:AssociateApplications' :: NonEmpty Text
applicationIDs = NonEmpty Text
a} :: AssociateApplications) 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

-- | Wave ID.
associateApplications_waveID :: Lens.Lens' AssociateApplications Prelude.Text
associateApplications_waveID :: Lens' AssociateApplications Text
associateApplications_waveID = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AssociateApplications' {Text
waveID :: Text
$sel:waveID:AssociateApplications' :: AssociateApplications -> Text
waveID} -> Text
waveID) (\s :: AssociateApplications
s@AssociateApplications' {} Text
a -> AssociateApplications
s {$sel:waveID:AssociateApplications' :: Text
waveID = Text
a} :: AssociateApplications)

instance Core.AWSRequest AssociateApplications where
  type
    AWSResponse AssociateApplications =
      AssociateApplicationsResponse
  request :: (Service -> Service)
-> AssociateApplications -> Request AssociateApplications
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 AssociateApplications
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse AssociateApplications)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> () -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveEmpty
      ( \Int
s ResponseHeaders
h ()
x ->
          Int -> AssociateApplicationsResponse
AssociateApplicationsResponse'
            forall (f :: * -> *) a b. Functor 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 AssociateApplications where
  hashWithSalt :: Int -> AssociateApplications -> Int
hashWithSalt Int
_salt AssociateApplications' {NonEmpty Text
Text
waveID :: Text
applicationIDs :: NonEmpty Text
$sel:waveID:AssociateApplications' :: AssociateApplications -> Text
$sel:applicationIDs:AssociateApplications' :: AssociateApplications -> NonEmpty Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` NonEmpty Text
applicationIDs
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
waveID

instance Prelude.NFData AssociateApplications where
  rnf :: AssociateApplications -> ()
rnf AssociateApplications' {NonEmpty Text
Text
waveID :: Text
applicationIDs :: NonEmpty Text
$sel:waveID:AssociateApplications' :: AssociateApplications -> Text
$sel:applicationIDs:AssociateApplications' :: AssociateApplications -> NonEmpty Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf NonEmpty Text
applicationIDs
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
waveID

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

instance Data.ToJSON AssociateApplications where
  toJSON :: AssociateApplications -> Value
toJSON AssociateApplications' {NonEmpty Text
Text
waveID :: Text
applicationIDs :: NonEmpty Text
$sel:waveID:AssociateApplications' :: AssociateApplications -> Text
$sel:applicationIDs:AssociateApplications' :: AssociateApplications -> NonEmpty Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ forall a. a -> Maybe a
Prelude.Just
              (Key
"applicationIDs" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= NonEmpty Text
applicationIDs),
            forall a. a -> Maybe a
Prelude.Just (Key
"waveID" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
waveID)
          ]
      )

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

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

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

-- |
-- Create a value of 'AssociateApplicationsResponse' 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:
--
-- 'httpStatus', 'associateApplicationsResponse_httpStatus' - The response's http status code.
newAssociateApplicationsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  AssociateApplicationsResponse
newAssociateApplicationsResponse :: Int -> AssociateApplicationsResponse
newAssociateApplicationsResponse Int
pHttpStatus_ =
  AssociateApplicationsResponse'
    { $sel:httpStatus:AssociateApplicationsResponse' :: Int
httpStatus =
        Int
pHttpStatus_
    }

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

instance Prelude.NFData AssociateApplicationsResponse where
  rnf :: AssociateApplicationsResponse -> ()
rnf AssociateApplicationsResponse' {Int
httpStatus :: Int
$sel:httpStatus:AssociateApplicationsResponse' :: AssociateApplicationsResponse -> Int
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus