{-# 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.MediaConnect.RemoveFlowSource
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Removes a source from an existing flow. This request can be made only if
-- there is more than one source on the flow.
module Amazonka.MediaConnect.RemoveFlowSource
  ( -- * Creating a Request
    RemoveFlowSource (..),
    newRemoveFlowSource,

    -- * Request Lenses
    removeFlowSource_flowArn,
    removeFlowSource_sourceArn,

    -- * Destructuring the Response
    RemoveFlowSourceResponse (..),
    newRemoveFlowSourceResponse,

    -- * Response Lenses
    removeFlowSourceResponse_flowArn,
    removeFlowSourceResponse_sourceArn,
    removeFlowSourceResponse_httpStatus,
  )
where

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

-- | /See:/ 'newRemoveFlowSource' smart constructor.
data RemoveFlowSource = RemoveFlowSource'
  { -- | The flow that you want to remove a source from.
    RemoveFlowSource -> Text
flowArn :: Prelude.Text,
    -- | The ARN of the source that you want to remove.
    RemoveFlowSource -> Text
sourceArn :: Prelude.Text
  }
  deriving (RemoveFlowSource -> RemoveFlowSource -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RemoveFlowSource -> RemoveFlowSource -> Bool
$c/= :: RemoveFlowSource -> RemoveFlowSource -> Bool
== :: RemoveFlowSource -> RemoveFlowSource -> Bool
$c== :: RemoveFlowSource -> RemoveFlowSource -> Bool
Prelude.Eq, ReadPrec [RemoveFlowSource]
ReadPrec RemoveFlowSource
Int -> ReadS RemoveFlowSource
ReadS [RemoveFlowSource]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [RemoveFlowSource]
$creadListPrec :: ReadPrec [RemoveFlowSource]
readPrec :: ReadPrec RemoveFlowSource
$creadPrec :: ReadPrec RemoveFlowSource
readList :: ReadS [RemoveFlowSource]
$creadList :: ReadS [RemoveFlowSource]
readsPrec :: Int -> ReadS RemoveFlowSource
$creadsPrec :: Int -> ReadS RemoveFlowSource
Prelude.Read, Int -> RemoveFlowSource -> ShowS
[RemoveFlowSource] -> ShowS
RemoveFlowSource -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RemoveFlowSource] -> ShowS
$cshowList :: [RemoveFlowSource] -> ShowS
show :: RemoveFlowSource -> String
$cshow :: RemoveFlowSource -> String
showsPrec :: Int -> RemoveFlowSource -> ShowS
$cshowsPrec :: Int -> RemoveFlowSource -> ShowS
Prelude.Show, forall x. Rep RemoveFlowSource x -> RemoveFlowSource
forall x. RemoveFlowSource -> Rep RemoveFlowSource x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RemoveFlowSource x -> RemoveFlowSource
$cfrom :: forall x. RemoveFlowSource -> Rep RemoveFlowSource x
Prelude.Generic)

-- |
-- Create a value of 'RemoveFlowSource' 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:
--
-- 'flowArn', 'removeFlowSource_flowArn' - The flow that you want to remove a source from.
--
-- 'sourceArn', 'removeFlowSource_sourceArn' - The ARN of the source that you want to remove.
newRemoveFlowSource ::
  -- | 'flowArn'
  Prelude.Text ->
  -- | 'sourceArn'
  Prelude.Text ->
  RemoveFlowSource
newRemoveFlowSource :: Text -> Text -> RemoveFlowSource
newRemoveFlowSource Text
pFlowArn_ Text
pSourceArn_ =
  RemoveFlowSource'
    { $sel:flowArn:RemoveFlowSource' :: Text
flowArn = Text
pFlowArn_,
      $sel:sourceArn:RemoveFlowSource' :: Text
sourceArn = Text
pSourceArn_
    }

-- | The flow that you want to remove a source from.
removeFlowSource_flowArn :: Lens.Lens' RemoveFlowSource Prelude.Text
removeFlowSource_flowArn :: Lens' RemoveFlowSource Text
removeFlowSource_flowArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RemoveFlowSource' {Text
flowArn :: Text
$sel:flowArn:RemoveFlowSource' :: RemoveFlowSource -> Text
flowArn} -> Text
flowArn) (\s :: RemoveFlowSource
s@RemoveFlowSource' {} Text
a -> RemoveFlowSource
s {$sel:flowArn:RemoveFlowSource' :: Text
flowArn = Text
a} :: RemoveFlowSource)

-- | The ARN of the source that you want to remove.
removeFlowSource_sourceArn :: Lens.Lens' RemoveFlowSource Prelude.Text
removeFlowSource_sourceArn :: Lens' RemoveFlowSource Text
removeFlowSource_sourceArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RemoveFlowSource' {Text
sourceArn :: Text
$sel:sourceArn:RemoveFlowSource' :: RemoveFlowSource -> Text
sourceArn} -> Text
sourceArn) (\s :: RemoveFlowSource
s@RemoveFlowSource' {} Text
a -> RemoveFlowSource
s {$sel:sourceArn:RemoveFlowSource' :: Text
sourceArn = Text
a} :: RemoveFlowSource)

instance Core.AWSRequest RemoveFlowSource where
  type
    AWSResponse RemoveFlowSource =
      RemoveFlowSourceResponse
  request :: (Service -> Service)
-> RemoveFlowSource -> Request RemoveFlowSource
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.delete (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy RemoveFlowSource
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse RemoveFlowSource)))
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 -> Maybe Text -> Int -> RemoveFlowSourceResponse
RemoveFlowSourceResponse'
            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
"flowArn")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"sourceArn")
            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 RemoveFlowSource where
  hashWithSalt :: Int -> RemoveFlowSource -> Int
hashWithSalt Int
_salt RemoveFlowSource' {Text
sourceArn :: Text
flowArn :: Text
$sel:sourceArn:RemoveFlowSource' :: RemoveFlowSource -> Text
$sel:flowArn:RemoveFlowSource' :: RemoveFlowSource -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
flowArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
sourceArn

instance Prelude.NFData RemoveFlowSource where
  rnf :: RemoveFlowSource -> ()
rnf RemoveFlowSource' {Text
sourceArn :: Text
flowArn :: Text
$sel:sourceArn:RemoveFlowSource' :: RemoveFlowSource -> Text
$sel:flowArn:RemoveFlowSource' :: RemoveFlowSource -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
flowArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
sourceArn

instance Data.ToHeaders RemoveFlowSource where
  toHeaders :: RemoveFlowSource -> 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.ToPath RemoveFlowSource where
  toPath :: RemoveFlowSource -> ByteString
toPath RemoveFlowSource' {Text
sourceArn :: Text
flowArn :: Text
$sel:sourceArn:RemoveFlowSource' :: RemoveFlowSource -> Text
$sel:flowArn:RemoveFlowSource' :: RemoveFlowSource -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/v1/flows/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
flowArn,
        ByteString
"/source/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
sourceArn
      ]

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

-- | /See:/ 'newRemoveFlowSourceResponse' smart constructor.
data RemoveFlowSourceResponse = RemoveFlowSourceResponse'
  { -- | The ARN of the flow that is associated with the source you removed.
    RemoveFlowSourceResponse -> Maybe Text
flowArn :: Prelude.Maybe Prelude.Text,
    -- | The ARN of the source that was removed.
    RemoveFlowSourceResponse -> Maybe Text
sourceArn :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    RemoveFlowSourceResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (RemoveFlowSourceResponse -> RemoveFlowSourceResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RemoveFlowSourceResponse -> RemoveFlowSourceResponse -> Bool
$c/= :: RemoveFlowSourceResponse -> RemoveFlowSourceResponse -> Bool
== :: RemoveFlowSourceResponse -> RemoveFlowSourceResponse -> Bool
$c== :: RemoveFlowSourceResponse -> RemoveFlowSourceResponse -> Bool
Prelude.Eq, ReadPrec [RemoveFlowSourceResponse]
ReadPrec RemoveFlowSourceResponse
Int -> ReadS RemoveFlowSourceResponse
ReadS [RemoveFlowSourceResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [RemoveFlowSourceResponse]
$creadListPrec :: ReadPrec [RemoveFlowSourceResponse]
readPrec :: ReadPrec RemoveFlowSourceResponse
$creadPrec :: ReadPrec RemoveFlowSourceResponse
readList :: ReadS [RemoveFlowSourceResponse]
$creadList :: ReadS [RemoveFlowSourceResponse]
readsPrec :: Int -> ReadS RemoveFlowSourceResponse
$creadsPrec :: Int -> ReadS RemoveFlowSourceResponse
Prelude.Read, Int -> RemoveFlowSourceResponse -> ShowS
[RemoveFlowSourceResponse] -> ShowS
RemoveFlowSourceResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RemoveFlowSourceResponse] -> ShowS
$cshowList :: [RemoveFlowSourceResponse] -> ShowS
show :: RemoveFlowSourceResponse -> String
$cshow :: RemoveFlowSourceResponse -> String
showsPrec :: Int -> RemoveFlowSourceResponse -> ShowS
$cshowsPrec :: Int -> RemoveFlowSourceResponse -> ShowS
Prelude.Show, forall x.
Rep RemoveFlowSourceResponse x -> RemoveFlowSourceResponse
forall x.
RemoveFlowSourceResponse -> Rep RemoveFlowSourceResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep RemoveFlowSourceResponse x -> RemoveFlowSourceResponse
$cfrom :: forall x.
RemoveFlowSourceResponse -> Rep RemoveFlowSourceResponse x
Prelude.Generic)

-- |
-- Create a value of 'RemoveFlowSourceResponse' 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:
--
-- 'flowArn', 'removeFlowSourceResponse_flowArn' - The ARN of the flow that is associated with the source you removed.
--
-- 'sourceArn', 'removeFlowSourceResponse_sourceArn' - The ARN of the source that was removed.
--
-- 'httpStatus', 'removeFlowSourceResponse_httpStatus' - The response's http status code.
newRemoveFlowSourceResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  RemoveFlowSourceResponse
newRemoveFlowSourceResponse :: Int -> RemoveFlowSourceResponse
newRemoveFlowSourceResponse Int
pHttpStatus_ =
  RemoveFlowSourceResponse'
    { $sel:flowArn:RemoveFlowSourceResponse' :: Maybe Text
flowArn =
        forall a. Maybe a
Prelude.Nothing,
      $sel:sourceArn:RemoveFlowSourceResponse' :: Maybe Text
sourceArn = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:RemoveFlowSourceResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The ARN of the flow that is associated with the source you removed.
removeFlowSourceResponse_flowArn :: Lens.Lens' RemoveFlowSourceResponse (Prelude.Maybe Prelude.Text)
removeFlowSourceResponse_flowArn :: Lens' RemoveFlowSourceResponse (Maybe Text)
removeFlowSourceResponse_flowArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RemoveFlowSourceResponse' {Maybe Text
flowArn :: Maybe Text
$sel:flowArn:RemoveFlowSourceResponse' :: RemoveFlowSourceResponse -> Maybe Text
flowArn} -> Maybe Text
flowArn) (\s :: RemoveFlowSourceResponse
s@RemoveFlowSourceResponse' {} Maybe Text
a -> RemoveFlowSourceResponse
s {$sel:flowArn:RemoveFlowSourceResponse' :: Maybe Text
flowArn = Maybe Text
a} :: RemoveFlowSourceResponse)

-- | The ARN of the source that was removed.
removeFlowSourceResponse_sourceArn :: Lens.Lens' RemoveFlowSourceResponse (Prelude.Maybe Prelude.Text)
removeFlowSourceResponse_sourceArn :: Lens' RemoveFlowSourceResponse (Maybe Text)
removeFlowSourceResponse_sourceArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RemoveFlowSourceResponse' {Maybe Text
sourceArn :: Maybe Text
$sel:sourceArn:RemoveFlowSourceResponse' :: RemoveFlowSourceResponse -> Maybe Text
sourceArn} -> Maybe Text
sourceArn) (\s :: RemoveFlowSourceResponse
s@RemoveFlowSourceResponse' {} Maybe Text
a -> RemoveFlowSourceResponse
s {$sel:sourceArn:RemoveFlowSourceResponse' :: Maybe Text
sourceArn = Maybe Text
a} :: RemoveFlowSourceResponse)

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

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