{-# 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.DeleteVodSource
-- 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 video on demand (VOD) source to delete.
module Amazonka.MediaTailor.DeleteVodSource
  ( -- * Creating a Request
    DeleteVodSource (..),
    newDeleteVodSource,

    -- * Request Lenses
    deleteVodSource_sourceLocationName,
    deleteVodSource_vodSourceName,

    -- * Destructuring the Response
    DeleteVodSourceResponse (..),
    newDeleteVodSourceResponse,

    -- * Response Lenses
    deleteVodSourceResponse_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:/ 'newDeleteVodSource' smart constructor.
data DeleteVodSource = DeleteVodSource'
  { -- | The name of the source location associated with this VOD Source.
    DeleteVodSource -> Text
sourceLocationName :: Prelude.Text,
    -- | The name of the VOD source.
    DeleteVodSource -> Text
vodSourceName :: Prelude.Text
  }
  deriving (DeleteVodSource -> DeleteVodSource -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteVodSource -> DeleteVodSource -> Bool
$c/= :: DeleteVodSource -> DeleteVodSource -> Bool
== :: DeleteVodSource -> DeleteVodSource -> Bool
$c== :: DeleteVodSource -> DeleteVodSource -> Bool
Prelude.Eq, ReadPrec [DeleteVodSource]
ReadPrec DeleteVodSource
Int -> ReadS DeleteVodSource
ReadS [DeleteVodSource]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteVodSource]
$creadListPrec :: ReadPrec [DeleteVodSource]
readPrec :: ReadPrec DeleteVodSource
$creadPrec :: ReadPrec DeleteVodSource
readList :: ReadS [DeleteVodSource]
$creadList :: ReadS [DeleteVodSource]
readsPrec :: Int -> ReadS DeleteVodSource
$creadsPrec :: Int -> ReadS DeleteVodSource
Prelude.Read, Int -> DeleteVodSource -> ShowS
[DeleteVodSource] -> ShowS
DeleteVodSource -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteVodSource] -> ShowS
$cshowList :: [DeleteVodSource] -> ShowS
show :: DeleteVodSource -> String
$cshow :: DeleteVodSource -> String
showsPrec :: Int -> DeleteVodSource -> ShowS
$cshowsPrec :: Int -> DeleteVodSource -> ShowS
Prelude.Show, forall x. Rep DeleteVodSource x -> DeleteVodSource
forall x. DeleteVodSource -> Rep DeleteVodSource x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteVodSource x -> DeleteVodSource
$cfrom :: forall x. DeleteVodSource -> Rep DeleteVodSource x
Prelude.Generic)

-- |
-- Create a value of 'DeleteVodSource' 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:
--
-- 'sourceLocationName', 'deleteVodSource_sourceLocationName' - The name of the source location associated with this VOD Source.
--
-- 'vodSourceName', 'deleteVodSource_vodSourceName' - The name of the VOD source.
newDeleteVodSource ::
  -- | 'sourceLocationName'
  Prelude.Text ->
  -- | 'vodSourceName'
  Prelude.Text ->
  DeleteVodSource
newDeleteVodSource :: Text -> Text -> DeleteVodSource
newDeleteVodSource
  Text
pSourceLocationName_
  Text
pVodSourceName_ =
    DeleteVodSource'
      { $sel:sourceLocationName:DeleteVodSource' :: Text
sourceLocationName =
          Text
pSourceLocationName_,
        $sel:vodSourceName:DeleteVodSource' :: Text
vodSourceName = Text
pVodSourceName_
      }

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

-- | The name of the VOD source.
deleteVodSource_vodSourceName :: Lens.Lens' DeleteVodSource Prelude.Text
deleteVodSource_vodSourceName :: Lens' DeleteVodSource Text
deleteVodSource_vodSourceName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteVodSource' {Text
vodSourceName :: Text
$sel:vodSourceName:DeleteVodSource' :: DeleteVodSource -> Text
vodSourceName} -> Text
vodSourceName) (\s :: DeleteVodSource
s@DeleteVodSource' {} Text
a -> DeleteVodSource
s {$sel:vodSourceName:DeleteVodSource' :: Text
vodSourceName = Text
a} :: DeleteVodSource)

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

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

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

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

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

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

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

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