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

    -- * Request Lenses
    disassociateApplications_applicationIDs,
    disassociateApplications_waveID,

    -- * Destructuring the Response
    DisassociateApplicationsResponse (..),
    newDisassociateApplicationsResponse,

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

-- |
-- Create a value of 'DisassociateApplications' 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', 'disassociateApplications_applicationIDs' - Application IDs list.
--
-- 'waveID', 'disassociateApplications_waveID' - Wave ID.
newDisassociateApplications ::
  -- | 'applicationIDs'
  Prelude.NonEmpty Prelude.Text ->
  -- | 'waveID'
  Prelude.Text ->
  DisassociateApplications
newDisassociateApplications :: NonEmpty Text -> Text -> DisassociateApplications
newDisassociateApplications NonEmpty Text
pApplicationIDs_ Text
pWaveID_ =
  DisassociateApplications'
    { $sel:applicationIDs:DisassociateApplications' :: 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:DisassociateApplications' :: Text
waveID = Text
pWaveID_
    }

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

instance Core.AWSRequest DisassociateApplications where
  type
    AWSResponse DisassociateApplications =
      DisassociateApplicationsResponse
  request :: (Service -> Service)
-> DisassociateApplications -> Request DisassociateApplications
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 DisassociateApplications
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DisassociateApplications)))
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 -> DisassociateApplicationsResponse
DisassociateApplicationsResponse'
            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 DisassociateApplications where
  hashWithSalt :: Int -> DisassociateApplications -> Int
hashWithSalt Int
_salt DisassociateApplications' {NonEmpty Text
Text
waveID :: Text
applicationIDs :: NonEmpty Text
$sel:waveID:DisassociateApplications' :: DisassociateApplications -> Text
$sel:applicationIDs:DisassociateApplications' :: DisassociateApplications -> 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 DisassociateApplications where
  rnf :: DisassociateApplications -> ()
rnf DisassociateApplications' {NonEmpty Text
Text
waveID :: Text
applicationIDs :: NonEmpty Text
$sel:waveID:DisassociateApplications' :: DisassociateApplications -> Text
$sel:applicationIDs:DisassociateApplications' :: DisassociateApplications -> 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 DisassociateApplications where
  toHeaders :: DisassociateApplications -> 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 DisassociateApplications where
  toJSON :: DisassociateApplications -> Value
toJSON DisassociateApplications' {NonEmpty Text
Text
waveID :: Text
applicationIDs :: NonEmpty Text
$sel:waveID:DisassociateApplications' :: DisassociateApplications -> Text
$sel:applicationIDs:DisassociateApplications' :: DisassociateApplications -> 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 DisassociateApplications where
  toPath :: DisassociateApplications -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/DisassociateApplications"

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

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

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

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

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