{-# 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.DescribeVodSource
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Provides details about a specific video on demand (VOD) source in a
-- specific source location.
module Amazonka.MediaTailor.DescribeVodSource
  ( -- * Creating a Request
    DescribeVodSource (..),
    newDescribeVodSource,

    -- * Request Lenses
    describeVodSource_sourceLocationName,
    describeVodSource_vodSourceName,

    -- * Destructuring the Response
    DescribeVodSourceResponse (..),
    newDescribeVodSourceResponse,

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

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

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

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

instance Core.AWSRequest DescribeVodSource where
  type
    AWSResponse DescribeVodSource =
      DescribeVodSourceResponse
  request :: (Service -> Service)
-> DescribeVodSource -> Request DescribeVodSource
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.get (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy DescribeVodSource
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DescribeVodSource)))
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 POSIX
-> Maybe [HttpPackageConfiguration]
-> Maybe POSIX
-> Maybe Text
-> Maybe (HashMap Text Text)
-> Maybe Text
-> Int
-> DescribeVodSourceResponse
DescribeVodSourceResponse'
            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
"Arn")
            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
"CreationTime")
            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
"HttpPackageConfigurations"
                            forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                        )
            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
"LastModifiedTime")
            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
"SourceLocationName")
            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
"tags" forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty)
            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
"VodSourceName")
            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 DescribeVodSource where
  hashWithSalt :: Int -> DescribeVodSource -> Int
hashWithSalt Int
_salt DescribeVodSource' {Text
vodSourceName :: Text
sourceLocationName :: Text
$sel:vodSourceName:DescribeVodSource' :: DescribeVodSource -> Text
$sel:sourceLocationName:DescribeVodSource' :: DescribeVodSource -> 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 DescribeVodSource where
  rnf :: DescribeVodSource -> ()
rnf DescribeVodSource' {Text
vodSourceName :: Text
sourceLocationName :: Text
$sel:vodSourceName:DescribeVodSource' :: DescribeVodSource -> Text
$sel:sourceLocationName:DescribeVodSource' :: DescribeVodSource -> 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 DescribeVodSource where
  toHeaders :: DescribeVodSource -> 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 DescribeVodSource where
  toPath :: DescribeVodSource -> ByteString
toPath DescribeVodSource' {Text
vodSourceName :: Text
sourceLocationName :: Text
$sel:vodSourceName:DescribeVodSource' :: DescribeVodSource -> Text
$sel:sourceLocationName:DescribeVodSource' :: DescribeVodSource -> 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 DescribeVodSource where
  toQuery :: DescribeVodSource -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

-- | /See:/ 'newDescribeVodSourceResponse' smart constructor.
data DescribeVodSourceResponse = DescribeVodSourceResponse'
  { -- | The ARN of the VOD source.
    DescribeVodSourceResponse -> Maybe Text
arn :: Prelude.Maybe Prelude.Text,
    -- | The timestamp that indicates when the VOD source was created.
    DescribeVodSourceResponse -> Maybe POSIX
creationTime :: Prelude.Maybe Data.POSIX,
    -- | The HTTP package configurations.
    DescribeVodSourceResponse -> Maybe [HttpPackageConfiguration]
httpPackageConfigurations :: Prelude.Maybe [HttpPackageConfiguration],
    -- | The last modified time of the VOD source.
    DescribeVodSourceResponse -> Maybe POSIX
lastModifiedTime :: Prelude.Maybe Data.POSIX,
    -- | The name of the source location associated with the VOD source.
    DescribeVodSourceResponse -> Maybe Text
sourceLocationName :: Prelude.Maybe Prelude.Text,
    -- | The tags assigned to the VOD source. Tags are key-value pairs that you
    -- can associate with Amazon resources to help with organization, access
    -- control, and cost tracking. For more information, see
    -- <https://docs.aws.amazon.com/mediatailor/latest/ug/tagging.html Tagging AWS Elemental MediaTailor Resources>.
    DescribeVodSourceResponse -> Maybe (HashMap Text Text)
tags :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | The name of the VOD source.
    DescribeVodSourceResponse -> Maybe Text
vodSourceName :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    DescribeVodSourceResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DescribeVodSourceResponse -> DescribeVodSourceResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeVodSourceResponse -> DescribeVodSourceResponse -> Bool
$c/= :: DescribeVodSourceResponse -> DescribeVodSourceResponse -> Bool
== :: DescribeVodSourceResponse -> DescribeVodSourceResponse -> Bool
$c== :: DescribeVodSourceResponse -> DescribeVodSourceResponse -> Bool
Prelude.Eq, ReadPrec [DescribeVodSourceResponse]
ReadPrec DescribeVodSourceResponse
Int -> ReadS DescribeVodSourceResponse
ReadS [DescribeVodSourceResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeVodSourceResponse]
$creadListPrec :: ReadPrec [DescribeVodSourceResponse]
readPrec :: ReadPrec DescribeVodSourceResponse
$creadPrec :: ReadPrec DescribeVodSourceResponse
readList :: ReadS [DescribeVodSourceResponse]
$creadList :: ReadS [DescribeVodSourceResponse]
readsPrec :: Int -> ReadS DescribeVodSourceResponse
$creadsPrec :: Int -> ReadS DescribeVodSourceResponse
Prelude.Read, Int -> DescribeVodSourceResponse -> ShowS
[DescribeVodSourceResponse] -> ShowS
DescribeVodSourceResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeVodSourceResponse] -> ShowS
$cshowList :: [DescribeVodSourceResponse] -> ShowS
show :: DescribeVodSourceResponse -> String
$cshow :: DescribeVodSourceResponse -> String
showsPrec :: Int -> DescribeVodSourceResponse -> ShowS
$cshowsPrec :: Int -> DescribeVodSourceResponse -> ShowS
Prelude.Show, forall x.
Rep DescribeVodSourceResponse x -> DescribeVodSourceResponse
forall x.
DescribeVodSourceResponse -> Rep DescribeVodSourceResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeVodSourceResponse x -> DescribeVodSourceResponse
$cfrom :: forall x.
DescribeVodSourceResponse -> Rep DescribeVodSourceResponse x
Prelude.Generic)

-- |
-- Create a value of 'DescribeVodSourceResponse' 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:
--
-- 'arn', 'describeVodSourceResponse_arn' - The ARN of the VOD source.
--
-- 'creationTime', 'describeVodSourceResponse_creationTime' - The timestamp that indicates when the VOD source was created.
--
-- 'httpPackageConfigurations', 'describeVodSourceResponse_httpPackageConfigurations' - The HTTP package configurations.
--
-- 'lastModifiedTime', 'describeVodSourceResponse_lastModifiedTime' - The last modified time of the VOD source.
--
-- 'sourceLocationName', 'describeVodSourceResponse_sourceLocationName' - The name of the source location associated with the VOD source.
--
-- 'tags', 'describeVodSourceResponse_tags' - The tags assigned to the VOD source. Tags are key-value pairs that you
-- can associate with Amazon resources to help with organization, access
-- control, and cost tracking. For more information, see
-- <https://docs.aws.amazon.com/mediatailor/latest/ug/tagging.html Tagging AWS Elemental MediaTailor Resources>.
--
-- 'vodSourceName', 'describeVodSourceResponse_vodSourceName' - The name of the VOD source.
--
-- 'httpStatus', 'describeVodSourceResponse_httpStatus' - The response's http status code.
newDescribeVodSourceResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DescribeVodSourceResponse
newDescribeVodSourceResponse :: Int -> DescribeVodSourceResponse
newDescribeVodSourceResponse Int
pHttpStatus_ =
  DescribeVodSourceResponse'
    { $sel:arn:DescribeVodSourceResponse' :: Maybe Text
arn = forall a. Maybe a
Prelude.Nothing,
      $sel:creationTime:DescribeVodSourceResponse' :: Maybe POSIX
creationTime = forall a. Maybe a
Prelude.Nothing,
      $sel:httpPackageConfigurations:DescribeVodSourceResponse' :: Maybe [HttpPackageConfiguration]
httpPackageConfigurations = forall a. Maybe a
Prelude.Nothing,
      $sel:lastModifiedTime:DescribeVodSourceResponse' :: Maybe POSIX
lastModifiedTime = forall a. Maybe a
Prelude.Nothing,
      $sel:sourceLocationName:DescribeVodSourceResponse' :: Maybe Text
sourceLocationName = forall a. Maybe a
Prelude.Nothing,
      $sel:tags:DescribeVodSourceResponse' :: Maybe (HashMap Text Text)
tags = forall a. Maybe a
Prelude.Nothing,
      $sel:vodSourceName:DescribeVodSourceResponse' :: Maybe Text
vodSourceName = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DescribeVodSourceResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The ARN of the VOD source.
describeVodSourceResponse_arn :: Lens.Lens' DescribeVodSourceResponse (Prelude.Maybe Prelude.Text)
describeVodSourceResponse_arn :: Lens' DescribeVodSourceResponse (Maybe Text)
describeVodSourceResponse_arn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeVodSourceResponse' {Maybe Text
arn :: Maybe Text
$sel:arn:DescribeVodSourceResponse' :: DescribeVodSourceResponse -> Maybe Text
arn} -> Maybe Text
arn) (\s :: DescribeVodSourceResponse
s@DescribeVodSourceResponse' {} Maybe Text
a -> DescribeVodSourceResponse
s {$sel:arn:DescribeVodSourceResponse' :: Maybe Text
arn = Maybe Text
a} :: DescribeVodSourceResponse)

-- | The timestamp that indicates when the VOD source was created.
describeVodSourceResponse_creationTime :: Lens.Lens' DescribeVodSourceResponse (Prelude.Maybe Prelude.UTCTime)
describeVodSourceResponse_creationTime :: Lens' DescribeVodSourceResponse (Maybe UTCTime)
describeVodSourceResponse_creationTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeVodSourceResponse' {Maybe POSIX
creationTime :: Maybe POSIX
$sel:creationTime:DescribeVodSourceResponse' :: DescribeVodSourceResponse -> Maybe POSIX
creationTime} -> Maybe POSIX
creationTime) (\s :: DescribeVodSourceResponse
s@DescribeVodSourceResponse' {} Maybe POSIX
a -> DescribeVodSourceResponse
s {$sel:creationTime:DescribeVodSourceResponse' :: Maybe POSIX
creationTime = Maybe POSIX
a} :: DescribeVodSourceResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | The HTTP package configurations.
describeVodSourceResponse_httpPackageConfigurations :: Lens.Lens' DescribeVodSourceResponse (Prelude.Maybe [HttpPackageConfiguration])
describeVodSourceResponse_httpPackageConfigurations :: Lens' DescribeVodSourceResponse (Maybe [HttpPackageConfiguration])
describeVodSourceResponse_httpPackageConfigurations = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeVodSourceResponse' {Maybe [HttpPackageConfiguration]
httpPackageConfigurations :: Maybe [HttpPackageConfiguration]
$sel:httpPackageConfigurations:DescribeVodSourceResponse' :: DescribeVodSourceResponse -> Maybe [HttpPackageConfiguration]
httpPackageConfigurations} -> Maybe [HttpPackageConfiguration]
httpPackageConfigurations) (\s :: DescribeVodSourceResponse
s@DescribeVodSourceResponse' {} Maybe [HttpPackageConfiguration]
a -> DescribeVodSourceResponse
s {$sel:httpPackageConfigurations:DescribeVodSourceResponse' :: Maybe [HttpPackageConfiguration]
httpPackageConfigurations = Maybe [HttpPackageConfiguration]
a} :: DescribeVodSourceResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | The last modified time of the VOD source.
describeVodSourceResponse_lastModifiedTime :: Lens.Lens' DescribeVodSourceResponse (Prelude.Maybe Prelude.UTCTime)
describeVodSourceResponse_lastModifiedTime :: Lens' DescribeVodSourceResponse (Maybe UTCTime)
describeVodSourceResponse_lastModifiedTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeVodSourceResponse' {Maybe POSIX
lastModifiedTime :: Maybe POSIX
$sel:lastModifiedTime:DescribeVodSourceResponse' :: DescribeVodSourceResponse -> Maybe POSIX
lastModifiedTime} -> Maybe POSIX
lastModifiedTime) (\s :: DescribeVodSourceResponse
s@DescribeVodSourceResponse' {} Maybe POSIX
a -> DescribeVodSourceResponse
s {$sel:lastModifiedTime:DescribeVodSourceResponse' :: Maybe POSIX
lastModifiedTime = Maybe POSIX
a} :: DescribeVodSourceResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall (a :: Format). Iso' (Time a) UTCTime
Data._Time

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

-- | The tags assigned to the VOD source. Tags are key-value pairs that you
-- can associate with Amazon resources to help with organization, access
-- control, and cost tracking. For more information, see
-- <https://docs.aws.amazon.com/mediatailor/latest/ug/tagging.html Tagging AWS Elemental MediaTailor Resources>.
describeVodSourceResponse_tags :: Lens.Lens' DescribeVodSourceResponse (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
describeVodSourceResponse_tags :: Lens' DescribeVodSourceResponse (Maybe (HashMap Text Text))
describeVodSourceResponse_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeVodSourceResponse' {Maybe (HashMap Text Text)
tags :: Maybe (HashMap Text Text)
$sel:tags:DescribeVodSourceResponse' :: DescribeVodSourceResponse -> Maybe (HashMap Text Text)
tags} -> Maybe (HashMap Text Text)
tags) (\s :: DescribeVodSourceResponse
s@DescribeVodSourceResponse' {} Maybe (HashMap Text Text)
a -> DescribeVodSourceResponse
s {$sel:tags:DescribeVodSourceResponse' :: Maybe (HashMap Text Text)
tags = Maybe (HashMap Text Text)
a} :: DescribeVodSourceResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

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

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

instance Prelude.NFData DescribeVodSourceResponse where
  rnf :: DescribeVodSourceResponse -> ()
rnf DescribeVodSourceResponse' {Int
Maybe [HttpPackageConfiguration]
Maybe Text
Maybe (HashMap Text Text)
Maybe POSIX
httpStatus :: Int
vodSourceName :: Maybe Text
tags :: Maybe (HashMap Text Text)
sourceLocationName :: Maybe Text
lastModifiedTime :: Maybe POSIX
httpPackageConfigurations :: Maybe [HttpPackageConfiguration]
creationTime :: Maybe POSIX
arn :: Maybe Text
$sel:httpStatus:DescribeVodSourceResponse' :: DescribeVodSourceResponse -> Int
$sel:vodSourceName:DescribeVodSourceResponse' :: DescribeVodSourceResponse -> Maybe Text
$sel:tags:DescribeVodSourceResponse' :: DescribeVodSourceResponse -> Maybe (HashMap Text Text)
$sel:sourceLocationName:DescribeVodSourceResponse' :: DescribeVodSourceResponse -> Maybe Text
$sel:lastModifiedTime:DescribeVodSourceResponse' :: DescribeVodSourceResponse -> Maybe POSIX
$sel:httpPackageConfigurations:DescribeVodSourceResponse' :: DescribeVodSourceResponse -> Maybe [HttpPackageConfiguration]
$sel:creationTime:DescribeVodSourceResponse' :: DescribeVodSourceResponse -> Maybe POSIX
$sel:arn:DescribeVodSourceResponse' :: DescribeVodSourceResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
arn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
creationTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [HttpPackageConfiguration]
httpPackageConfigurations
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
lastModifiedTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
sourceLocationName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (HashMap Text Text)
tags
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
vodSourceName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus