{-# 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.MediaTailor.DeleteLiveSource
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- The live source to delete.
module Amazonka.MediaTailor.DeleteLiveSource
  ( -- * Creating a Request
    DeleteLiveSource (..),
    newDeleteLiveSource,

    -- * Request Lenses
    deleteLiveSource_liveSourceName,
    deleteLiveSource_sourceLocationName,

    -- * Destructuring the Response
    DeleteLiveSourceResponse (..),
    newDeleteLiveSourceResponse,

    -- * Response Lenses
    deleteLiveSourceResponse_httpStatus,
  )
where

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

-- | /See:/ 'newDeleteLiveSource' smart constructor.
data DeleteLiveSource = DeleteLiveSource'
  { -- | The name of the live source.
    DeleteLiveSource -> Text
liveSourceName :: Prelude.Text,
    -- | The name of the source location associated with this Live Source.
    DeleteLiveSource -> Text
sourceLocationName :: Prelude.Text
  }
  deriving (DeleteLiveSource -> DeleteLiveSource -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteLiveSource -> DeleteLiveSource -> Bool
$c/= :: DeleteLiveSource -> DeleteLiveSource -> Bool
== :: DeleteLiveSource -> DeleteLiveSource -> Bool
$c== :: DeleteLiveSource -> DeleteLiveSource -> Bool
Prelude.Eq, ReadPrec [DeleteLiveSource]
ReadPrec DeleteLiveSource
Int -> ReadS DeleteLiveSource
ReadS [DeleteLiveSource]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteLiveSource]
$creadListPrec :: ReadPrec [DeleteLiveSource]
readPrec :: ReadPrec DeleteLiveSource
$creadPrec :: ReadPrec DeleteLiveSource
readList :: ReadS [DeleteLiveSource]
$creadList :: ReadS [DeleteLiveSource]
readsPrec :: Int -> ReadS DeleteLiveSource
$creadsPrec :: Int -> ReadS DeleteLiveSource
Prelude.Read, Int -> DeleteLiveSource -> ShowS
[DeleteLiveSource] -> ShowS
DeleteLiveSource -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteLiveSource] -> ShowS
$cshowList :: [DeleteLiveSource] -> ShowS
show :: DeleteLiveSource -> String
$cshow :: DeleteLiveSource -> String
showsPrec :: Int -> DeleteLiveSource -> ShowS
$cshowsPrec :: Int -> DeleteLiveSource -> ShowS
Prelude.Show, forall x. Rep DeleteLiveSource x -> DeleteLiveSource
forall x. DeleteLiveSource -> Rep DeleteLiveSource x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteLiveSource x -> DeleteLiveSource
$cfrom :: forall x. DeleteLiveSource -> Rep DeleteLiveSource x
Prelude.Generic)

-- |
-- Create a value of 'DeleteLiveSource' 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:
--
-- 'liveSourceName', 'deleteLiveSource_liveSourceName' - The name of the live source.
--
-- 'sourceLocationName', 'deleteLiveSource_sourceLocationName' - The name of the source location associated with this Live Source.
newDeleteLiveSource ::
  -- | 'liveSourceName'
  Prelude.Text ->
  -- | 'sourceLocationName'
  Prelude.Text ->
  DeleteLiveSource
newDeleteLiveSource :: Text -> Text -> DeleteLiveSource
newDeleteLiveSource
  Text
pLiveSourceName_
  Text
pSourceLocationName_ =
    DeleteLiveSource'
      { $sel:liveSourceName:DeleteLiveSource' :: Text
liveSourceName =
          Text
pLiveSourceName_,
        $sel:sourceLocationName:DeleteLiveSource' :: Text
sourceLocationName = Text
pSourceLocationName_
      }

-- | The name of the live source.
deleteLiveSource_liveSourceName :: Lens.Lens' DeleteLiveSource Prelude.Text
deleteLiveSource_liveSourceName :: Lens' DeleteLiveSource Text
deleteLiveSource_liveSourceName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteLiveSource' {Text
liveSourceName :: Text
$sel:liveSourceName:DeleteLiveSource' :: DeleteLiveSource -> Text
liveSourceName} -> Text
liveSourceName) (\s :: DeleteLiveSource
s@DeleteLiveSource' {} Text
a -> DeleteLiveSource
s {$sel:liveSourceName:DeleteLiveSource' :: Text
liveSourceName = Text
a} :: DeleteLiveSource)

-- | The name of the source location associated with this Live Source.
deleteLiveSource_sourceLocationName :: Lens.Lens' DeleteLiveSource Prelude.Text
deleteLiveSource_sourceLocationName :: Lens' DeleteLiveSource Text
deleteLiveSource_sourceLocationName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteLiveSource' {Text
sourceLocationName :: Text
$sel:sourceLocationName:DeleteLiveSource' :: DeleteLiveSource -> Text
sourceLocationName} -> Text
sourceLocationName) (\s :: DeleteLiveSource
s@DeleteLiveSource' {} Text
a -> DeleteLiveSource
s {$sel:sourceLocationName:DeleteLiveSource' :: Text
sourceLocationName = Text
a} :: DeleteLiveSource)

instance Core.AWSRequest DeleteLiveSource where
  type
    AWSResponse DeleteLiveSource =
      DeleteLiveSourceResponse
  request :: (Service -> Service)
-> DeleteLiveSource -> Request DeleteLiveSource
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 DeleteLiveSource
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse DeleteLiveSource)))
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 -> DeleteLiveSourceResponse
DeleteLiveSourceResponse'
            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 DeleteLiveSource where
  hashWithSalt :: Int -> DeleteLiveSource -> Int
hashWithSalt Int
_salt DeleteLiveSource' {Text
sourceLocationName :: Text
liveSourceName :: Text
$sel:sourceLocationName:DeleteLiveSource' :: DeleteLiveSource -> Text
$sel:liveSourceName:DeleteLiveSource' :: DeleteLiveSource -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
liveSourceName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
sourceLocationName

instance Prelude.NFData DeleteLiveSource where
  rnf :: DeleteLiveSource -> ()
rnf DeleteLiveSource' {Text
sourceLocationName :: Text
liveSourceName :: Text
$sel:sourceLocationName:DeleteLiveSource' :: DeleteLiveSource -> Text
$sel:liveSourceName:DeleteLiveSource' :: DeleteLiveSource -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
liveSourceName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
sourceLocationName

instance Data.ToHeaders DeleteLiveSource where
  toHeaders :: DeleteLiveSource -> 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 DeleteLiveSource where
  toPath :: DeleteLiveSource -> ByteString
toPath DeleteLiveSource' {Text
sourceLocationName :: Text
liveSourceName :: Text
$sel:sourceLocationName:DeleteLiveSource' :: DeleteLiveSource -> Text
$sel:liveSourceName:DeleteLiveSource' :: DeleteLiveSource -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/sourceLocation/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
sourceLocationName,
        ByteString
"/liveSource/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
liveSourceName
      ]

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

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

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

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

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