{-# 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.DescribeSourceLocation
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Describes a source location. A source location is a container for
-- sources. For more information about source locations, see
-- <https://docs.aws.amazon.com/mediatailor/latest/ug/channel-assembly-source-locations.html Working with source locations>
-- in the /MediaTailor User Guide/.
module Amazonka.MediaTailor.DescribeSourceLocation
  ( -- * Creating a Request
    DescribeSourceLocation (..),
    newDescribeSourceLocation,

    -- * Request Lenses
    describeSourceLocation_sourceLocationName,

    -- * Destructuring the Response
    DescribeSourceLocationResponse (..),
    newDescribeSourceLocationResponse,

    -- * Response Lenses
    describeSourceLocationResponse_accessConfiguration,
    describeSourceLocationResponse_arn,
    describeSourceLocationResponse_creationTime,
    describeSourceLocationResponse_defaultSegmentDeliveryConfiguration,
    describeSourceLocationResponse_httpConfiguration,
    describeSourceLocationResponse_lastModifiedTime,
    describeSourceLocationResponse_segmentDeliveryConfigurations,
    describeSourceLocationResponse_sourceLocationName,
    describeSourceLocationResponse_tags,
    describeSourceLocationResponse_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:/ 'newDescribeSourceLocation' smart constructor.
data DescribeSourceLocation = DescribeSourceLocation'
  { -- | The name of the source location.
    DescribeSourceLocation -> Text
sourceLocationName :: Prelude.Text
  }
  deriving (DescribeSourceLocation -> DescribeSourceLocation -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeSourceLocation -> DescribeSourceLocation -> Bool
$c/= :: DescribeSourceLocation -> DescribeSourceLocation -> Bool
== :: DescribeSourceLocation -> DescribeSourceLocation -> Bool
$c== :: DescribeSourceLocation -> DescribeSourceLocation -> Bool
Prelude.Eq, ReadPrec [DescribeSourceLocation]
ReadPrec DescribeSourceLocation
Int -> ReadS DescribeSourceLocation
ReadS [DescribeSourceLocation]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeSourceLocation]
$creadListPrec :: ReadPrec [DescribeSourceLocation]
readPrec :: ReadPrec DescribeSourceLocation
$creadPrec :: ReadPrec DescribeSourceLocation
readList :: ReadS [DescribeSourceLocation]
$creadList :: ReadS [DescribeSourceLocation]
readsPrec :: Int -> ReadS DescribeSourceLocation
$creadsPrec :: Int -> ReadS DescribeSourceLocation
Prelude.Read, Int -> DescribeSourceLocation -> ShowS
[DescribeSourceLocation] -> ShowS
DescribeSourceLocation -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeSourceLocation] -> ShowS
$cshowList :: [DescribeSourceLocation] -> ShowS
show :: DescribeSourceLocation -> String
$cshow :: DescribeSourceLocation -> String
showsPrec :: Int -> DescribeSourceLocation -> ShowS
$cshowsPrec :: Int -> DescribeSourceLocation -> ShowS
Prelude.Show, forall x. Rep DescribeSourceLocation x -> DescribeSourceLocation
forall x. DescribeSourceLocation -> Rep DescribeSourceLocation x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DescribeSourceLocation x -> DescribeSourceLocation
$cfrom :: forall x. DescribeSourceLocation -> Rep DescribeSourceLocation x
Prelude.Generic)

-- |
-- Create a value of 'DescribeSourceLocation' 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', 'describeSourceLocation_sourceLocationName' - The name of the source location.
newDescribeSourceLocation ::
  -- | 'sourceLocationName'
  Prelude.Text ->
  DescribeSourceLocation
newDescribeSourceLocation :: Text -> DescribeSourceLocation
newDescribeSourceLocation Text
pSourceLocationName_ =
  DescribeSourceLocation'
    { $sel:sourceLocationName:DescribeSourceLocation' :: Text
sourceLocationName =
        Text
pSourceLocationName_
    }

-- | The name of the source location.
describeSourceLocation_sourceLocationName :: Lens.Lens' DescribeSourceLocation Prelude.Text
describeSourceLocation_sourceLocationName :: Lens' DescribeSourceLocation Text
describeSourceLocation_sourceLocationName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeSourceLocation' {Text
sourceLocationName :: Text
$sel:sourceLocationName:DescribeSourceLocation' :: DescribeSourceLocation -> Text
sourceLocationName} -> Text
sourceLocationName) (\s :: DescribeSourceLocation
s@DescribeSourceLocation' {} Text
a -> DescribeSourceLocation
s {$sel:sourceLocationName:DescribeSourceLocation' :: Text
sourceLocationName = Text
a} :: DescribeSourceLocation)

instance Core.AWSRequest DescribeSourceLocation where
  type
    AWSResponse DescribeSourceLocation =
      DescribeSourceLocationResponse
  request :: (Service -> Service)
-> DescribeSourceLocation -> Request DescribeSourceLocation
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 DescribeSourceLocation
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DescribeSourceLocation)))
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 AccessConfiguration
-> Maybe Text
-> Maybe POSIX
-> Maybe DefaultSegmentDeliveryConfiguration
-> Maybe HttpConfiguration
-> Maybe POSIX
-> Maybe [SegmentDeliveryConfiguration]
-> Maybe Text
-> Maybe (HashMap Text Text)
-> Int
-> DescribeSourceLocationResponse
DescribeSourceLocationResponse'
            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
"AccessConfiguration")
            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
"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
"DefaultSegmentDeliveryConfiguration")
            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
"HttpConfiguration")
            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
"SegmentDeliveryConfigurations"
                            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
"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.<*> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
      )

instance Prelude.Hashable DescribeSourceLocation where
  hashWithSalt :: Int -> DescribeSourceLocation -> Int
hashWithSalt Int
_salt DescribeSourceLocation' {Text
sourceLocationName :: Text
$sel:sourceLocationName:DescribeSourceLocation' :: DescribeSourceLocation -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
sourceLocationName

instance Prelude.NFData DescribeSourceLocation where
  rnf :: DescribeSourceLocation -> ()
rnf DescribeSourceLocation' {Text
sourceLocationName :: Text
$sel:sourceLocationName:DescribeSourceLocation' :: DescribeSourceLocation -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
sourceLocationName

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

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

-- | /See:/ 'newDescribeSourceLocationResponse' smart constructor.
data DescribeSourceLocationResponse = DescribeSourceLocationResponse'
  { -- | The access configuration for the source location.
    DescribeSourceLocationResponse -> Maybe AccessConfiguration
accessConfiguration :: Prelude.Maybe AccessConfiguration,
    -- | The ARN of the source location.
    DescribeSourceLocationResponse -> Maybe Text
arn :: Prelude.Maybe Prelude.Text,
    -- | The timestamp that indicates when the source location was created.
    DescribeSourceLocationResponse -> Maybe POSIX
creationTime :: Prelude.Maybe Data.POSIX,
    -- | The default segment delivery configuration settings.
    DescribeSourceLocationResponse
-> Maybe DefaultSegmentDeliveryConfiguration
defaultSegmentDeliveryConfiguration :: Prelude.Maybe DefaultSegmentDeliveryConfiguration,
    -- | The HTTP package configuration settings for the source location.
    DescribeSourceLocationResponse -> Maybe HttpConfiguration
httpConfiguration :: Prelude.Maybe HttpConfiguration,
    -- | The timestamp that indicates when the source location was last modified.
    DescribeSourceLocationResponse -> Maybe POSIX
lastModifiedTime :: Prelude.Maybe Data.POSIX,
    -- | A list of the segment delivery configurations associated with this
    -- resource.
    DescribeSourceLocationResponse
-> Maybe [SegmentDeliveryConfiguration]
segmentDeliveryConfigurations :: Prelude.Maybe [SegmentDeliveryConfiguration],
    -- | The name of the source location.
    DescribeSourceLocationResponse -> Maybe Text
sourceLocationName :: Prelude.Maybe Prelude.Text,
    -- | The tags assigned to the source location. 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>.
    DescribeSourceLocationResponse -> Maybe (HashMap Text Text)
tags :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | The response's http status code.
    DescribeSourceLocationResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DescribeSourceLocationResponse
-> DescribeSourceLocationResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeSourceLocationResponse
-> DescribeSourceLocationResponse -> Bool
$c/= :: DescribeSourceLocationResponse
-> DescribeSourceLocationResponse -> Bool
== :: DescribeSourceLocationResponse
-> DescribeSourceLocationResponse -> Bool
$c== :: DescribeSourceLocationResponse
-> DescribeSourceLocationResponse -> Bool
Prelude.Eq, ReadPrec [DescribeSourceLocationResponse]
ReadPrec DescribeSourceLocationResponse
Int -> ReadS DescribeSourceLocationResponse
ReadS [DescribeSourceLocationResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeSourceLocationResponse]
$creadListPrec :: ReadPrec [DescribeSourceLocationResponse]
readPrec :: ReadPrec DescribeSourceLocationResponse
$creadPrec :: ReadPrec DescribeSourceLocationResponse
readList :: ReadS [DescribeSourceLocationResponse]
$creadList :: ReadS [DescribeSourceLocationResponse]
readsPrec :: Int -> ReadS DescribeSourceLocationResponse
$creadsPrec :: Int -> ReadS DescribeSourceLocationResponse
Prelude.Read, Int -> DescribeSourceLocationResponse -> ShowS
[DescribeSourceLocationResponse] -> ShowS
DescribeSourceLocationResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeSourceLocationResponse] -> ShowS
$cshowList :: [DescribeSourceLocationResponse] -> ShowS
show :: DescribeSourceLocationResponse -> String
$cshow :: DescribeSourceLocationResponse -> String
showsPrec :: Int -> DescribeSourceLocationResponse -> ShowS
$cshowsPrec :: Int -> DescribeSourceLocationResponse -> ShowS
Prelude.Show, forall x.
Rep DescribeSourceLocationResponse x
-> DescribeSourceLocationResponse
forall x.
DescribeSourceLocationResponse
-> Rep DescribeSourceLocationResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeSourceLocationResponse x
-> DescribeSourceLocationResponse
$cfrom :: forall x.
DescribeSourceLocationResponse
-> Rep DescribeSourceLocationResponse x
Prelude.Generic)

-- |
-- Create a value of 'DescribeSourceLocationResponse' 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:
--
-- 'accessConfiguration', 'describeSourceLocationResponse_accessConfiguration' - The access configuration for the source location.
--
-- 'arn', 'describeSourceLocationResponse_arn' - The ARN of the source location.
--
-- 'creationTime', 'describeSourceLocationResponse_creationTime' - The timestamp that indicates when the source location was created.
--
-- 'defaultSegmentDeliveryConfiguration', 'describeSourceLocationResponse_defaultSegmentDeliveryConfiguration' - The default segment delivery configuration settings.
--
-- 'httpConfiguration', 'describeSourceLocationResponse_httpConfiguration' - The HTTP package configuration settings for the source location.
--
-- 'lastModifiedTime', 'describeSourceLocationResponse_lastModifiedTime' - The timestamp that indicates when the source location was last modified.
--
-- 'segmentDeliveryConfigurations', 'describeSourceLocationResponse_segmentDeliveryConfigurations' - A list of the segment delivery configurations associated with this
-- resource.
--
-- 'sourceLocationName', 'describeSourceLocationResponse_sourceLocationName' - The name of the source location.
--
-- 'tags', 'describeSourceLocationResponse_tags' - The tags assigned to the source location. 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>.
--
-- 'httpStatus', 'describeSourceLocationResponse_httpStatus' - The response's http status code.
newDescribeSourceLocationResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DescribeSourceLocationResponse
newDescribeSourceLocationResponse :: Int -> DescribeSourceLocationResponse
newDescribeSourceLocationResponse Int
pHttpStatus_ =
  DescribeSourceLocationResponse'
    { $sel:accessConfiguration:DescribeSourceLocationResponse' :: Maybe AccessConfiguration
accessConfiguration =
        forall a. Maybe a
Prelude.Nothing,
      $sel:arn:DescribeSourceLocationResponse' :: Maybe Text
arn = forall a. Maybe a
Prelude.Nothing,
      $sel:creationTime:DescribeSourceLocationResponse' :: Maybe POSIX
creationTime = forall a. Maybe a
Prelude.Nothing,
      $sel:defaultSegmentDeliveryConfiguration:DescribeSourceLocationResponse' :: Maybe DefaultSegmentDeliveryConfiguration
defaultSegmentDeliveryConfiguration =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpConfiguration:DescribeSourceLocationResponse' :: Maybe HttpConfiguration
httpConfiguration = forall a. Maybe a
Prelude.Nothing,
      $sel:lastModifiedTime:DescribeSourceLocationResponse' :: Maybe POSIX
lastModifiedTime = forall a. Maybe a
Prelude.Nothing,
      $sel:segmentDeliveryConfigurations:DescribeSourceLocationResponse' :: Maybe [SegmentDeliveryConfiguration]
segmentDeliveryConfigurations =
        forall a. Maybe a
Prelude.Nothing,
      $sel:sourceLocationName:DescribeSourceLocationResponse' :: Maybe Text
sourceLocationName = forall a. Maybe a
Prelude.Nothing,
      $sel:tags:DescribeSourceLocationResponse' :: Maybe (HashMap Text Text)
tags = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DescribeSourceLocationResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The access configuration for the source location.
describeSourceLocationResponse_accessConfiguration :: Lens.Lens' DescribeSourceLocationResponse (Prelude.Maybe AccessConfiguration)
describeSourceLocationResponse_accessConfiguration :: Lens' DescribeSourceLocationResponse (Maybe AccessConfiguration)
describeSourceLocationResponse_accessConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeSourceLocationResponse' {Maybe AccessConfiguration
accessConfiguration :: Maybe AccessConfiguration
$sel:accessConfiguration:DescribeSourceLocationResponse' :: DescribeSourceLocationResponse -> Maybe AccessConfiguration
accessConfiguration} -> Maybe AccessConfiguration
accessConfiguration) (\s :: DescribeSourceLocationResponse
s@DescribeSourceLocationResponse' {} Maybe AccessConfiguration
a -> DescribeSourceLocationResponse
s {$sel:accessConfiguration:DescribeSourceLocationResponse' :: Maybe AccessConfiguration
accessConfiguration = Maybe AccessConfiguration
a} :: DescribeSourceLocationResponse)

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

-- | The timestamp that indicates when the source location was created.
describeSourceLocationResponse_creationTime :: Lens.Lens' DescribeSourceLocationResponse (Prelude.Maybe Prelude.UTCTime)
describeSourceLocationResponse_creationTime :: Lens' DescribeSourceLocationResponse (Maybe UTCTime)
describeSourceLocationResponse_creationTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeSourceLocationResponse' {Maybe POSIX
creationTime :: Maybe POSIX
$sel:creationTime:DescribeSourceLocationResponse' :: DescribeSourceLocationResponse -> Maybe POSIX
creationTime} -> Maybe POSIX
creationTime) (\s :: DescribeSourceLocationResponse
s@DescribeSourceLocationResponse' {} Maybe POSIX
a -> DescribeSourceLocationResponse
s {$sel:creationTime:DescribeSourceLocationResponse' :: Maybe POSIX
creationTime = Maybe POSIX
a} :: DescribeSourceLocationResponse) 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 default segment delivery configuration settings.
describeSourceLocationResponse_defaultSegmentDeliveryConfiguration :: Lens.Lens' DescribeSourceLocationResponse (Prelude.Maybe DefaultSegmentDeliveryConfiguration)
describeSourceLocationResponse_defaultSegmentDeliveryConfiguration :: Lens'
  DescribeSourceLocationResponse
  (Maybe DefaultSegmentDeliveryConfiguration)
describeSourceLocationResponse_defaultSegmentDeliveryConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeSourceLocationResponse' {Maybe DefaultSegmentDeliveryConfiguration
defaultSegmentDeliveryConfiguration :: Maybe DefaultSegmentDeliveryConfiguration
$sel:defaultSegmentDeliveryConfiguration:DescribeSourceLocationResponse' :: DescribeSourceLocationResponse
-> Maybe DefaultSegmentDeliveryConfiguration
defaultSegmentDeliveryConfiguration} -> Maybe DefaultSegmentDeliveryConfiguration
defaultSegmentDeliveryConfiguration) (\s :: DescribeSourceLocationResponse
s@DescribeSourceLocationResponse' {} Maybe DefaultSegmentDeliveryConfiguration
a -> DescribeSourceLocationResponse
s {$sel:defaultSegmentDeliveryConfiguration:DescribeSourceLocationResponse' :: Maybe DefaultSegmentDeliveryConfiguration
defaultSegmentDeliveryConfiguration = Maybe DefaultSegmentDeliveryConfiguration
a} :: DescribeSourceLocationResponse)

-- | The HTTP package configuration settings for the source location.
describeSourceLocationResponse_httpConfiguration :: Lens.Lens' DescribeSourceLocationResponse (Prelude.Maybe HttpConfiguration)
describeSourceLocationResponse_httpConfiguration :: Lens' DescribeSourceLocationResponse (Maybe HttpConfiguration)
describeSourceLocationResponse_httpConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeSourceLocationResponse' {Maybe HttpConfiguration
httpConfiguration :: Maybe HttpConfiguration
$sel:httpConfiguration:DescribeSourceLocationResponse' :: DescribeSourceLocationResponse -> Maybe HttpConfiguration
httpConfiguration} -> Maybe HttpConfiguration
httpConfiguration) (\s :: DescribeSourceLocationResponse
s@DescribeSourceLocationResponse' {} Maybe HttpConfiguration
a -> DescribeSourceLocationResponse
s {$sel:httpConfiguration:DescribeSourceLocationResponse' :: Maybe HttpConfiguration
httpConfiguration = Maybe HttpConfiguration
a} :: DescribeSourceLocationResponse)

-- | The timestamp that indicates when the source location was last modified.
describeSourceLocationResponse_lastModifiedTime :: Lens.Lens' DescribeSourceLocationResponse (Prelude.Maybe Prelude.UTCTime)
describeSourceLocationResponse_lastModifiedTime :: Lens' DescribeSourceLocationResponse (Maybe UTCTime)
describeSourceLocationResponse_lastModifiedTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeSourceLocationResponse' {Maybe POSIX
lastModifiedTime :: Maybe POSIX
$sel:lastModifiedTime:DescribeSourceLocationResponse' :: DescribeSourceLocationResponse -> Maybe POSIX
lastModifiedTime} -> Maybe POSIX
lastModifiedTime) (\s :: DescribeSourceLocationResponse
s@DescribeSourceLocationResponse' {} Maybe POSIX
a -> DescribeSourceLocationResponse
s {$sel:lastModifiedTime:DescribeSourceLocationResponse' :: Maybe POSIX
lastModifiedTime = Maybe POSIX
a} :: DescribeSourceLocationResponse) 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

-- | A list of the segment delivery configurations associated with this
-- resource.
describeSourceLocationResponse_segmentDeliveryConfigurations :: Lens.Lens' DescribeSourceLocationResponse (Prelude.Maybe [SegmentDeliveryConfiguration])
describeSourceLocationResponse_segmentDeliveryConfigurations :: Lens'
  DescribeSourceLocationResponse
  (Maybe [SegmentDeliveryConfiguration])
describeSourceLocationResponse_segmentDeliveryConfigurations = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeSourceLocationResponse' {Maybe [SegmentDeliveryConfiguration]
segmentDeliveryConfigurations :: Maybe [SegmentDeliveryConfiguration]
$sel:segmentDeliveryConfigurations:DescribeSourceLocationResponse' :: DescribeSourceLocationResponse
-> Maybe [SegmentDeliveryConfiguration]
segmentDeliveryConfigurations} -> Maybe [SegmentDeliveryConfiguration]
segmentDeliveryConfigurations) (\s :: DescribeSourceLocationResponse
s@DescribeSourceLocationResponse' {} Maybe [SegmentDeliveryConfiguration]
a -> DescribeSourceLocationResponse
s {$sel:segmentDeliveryConfigurations:DescribeSourceLocationResponse' :: Maybe [SegmentDeliveryConfiguration]
segmentDeliveryConfigurations = Maybe [SegmentDeliveryConfiguration]
a} :: DescribeSourceLocationResponse) 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 source location.
describeSourceLocationResponse_sourceLocationName :: Lens.Lens' DescribeSourceLocationResponse (Prelude.Maybe Prelude.Text)
describeSourceLocationResponse_sourceLocationName :: Lens' DescribeSourceLocationResponse (Maybe Text)
describeSourceLocationResponse_sourceLocationName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeSourceLocationResponse' {Maybe Text
sourceLocationName :: Maybe Text
$sel:sourceLocationName:DescribeSourceLocationResponse' :: DescribeSourceLocationResponse -> Maybe Text
sourceLocationName} -> Maybe Text
sourceLocationName) (\s :: DescribeSourceLocationResponse
s@DescribeSourceLocationResponse' {} Maybe Text
a -> DescribeSourceLocationResponse
s {$sel:sourceLocationName:DescribeSourceLocationResponse' :: Maybe Text
sourceLocationName = Maybe Text
a} :: DescribeSourceLocationResponse)

-- | The tags assigned to the source location. 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>.
describeSourceLocationResponse_tags :: Lens.Lens' DescribeSourceLocationResponse (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
describeSourceLocationResponse_tags :: Lens' DescribeSourceLocationResponse (Maybe (HashMap Text Text))
describeSourceLocationResponse_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeSourceLocationResponse' {Maybe (HashMap Text Text)
tags :: Maybe (HashMap Text Text)
$sel:tags:DescribeSourceLocationResponse' :: DescribeSourceLocationResponse -> Maybe (HashMap Text Text)
tags} -> Maybe (HashMap Text Text)
tags) (\s :: DescribeSourceLocationResponse
s@DescribeSourceLocationResponse' {} Maybe (HashMap Text Text)
a -> DescribeSourceLocationResponse
s {$sel:tags:DescribeSourceLocationResponse' :: Maybe (HashMap Text Text)
tags = Maybe (HashMap Text Text)
a} :: DescribeSourceLocationResponse) 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 response's http status code.
describeSourceLocationResponse_httpStatus :: Lens.Lens' DescribeSourceLocationResponse Prelude.Int
describeSourceLocationResponse_httpStatus :: Lens' DescribeSourceLocationResponse Int
describeSourceLocationResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeSourceLocationResponse' {Int
httpStatus :: Int
$sel:httpStatus:DescribeSourceLocationResponse' :: DescribeSourceLocationResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: DescribeSourceLocationResponse
s@DescribeSourceLocationResponse' {} Int
a -> DescribeSourceLocationResponse
s {$sel:httpStatus:DescribeSourceLocationResponse' :: Int
httpStatus = Int
a} :: DescribeSourceLocationResponse)

instance
  Prelude.NFData
    DescribeSourceLocationResponse
  where
  rnf :: DescribeSourceLocationResponse -> ()
rnf DescribeSourceLocationResponse' {Int
Maybe [SegmentDeliveryConfiguration]
Maybe Text
Maybe (HashMap Text Text)
Maybe POSIX
Maybe DefaultSegmentDeliveryConfiguration
Maybe HttpConfiguration
Maybe AccessConfiguration
httpStatus :: Int
tags :: Maybe (HashMap Text Text)
sourceLocationName :: Maybe Text
segmentDeliveryConfigurations :: Maybe [SegmentDeliveryConfiguration]
lastModifiedTime :: Maybe POSIX
httpConfiguration :: Maybe HttpConfiguration
defaultSegmentDeliveryConfiguration :: Maybe DefaultSegmentDeliveryConfiguration
creationTime :: Maybe POSIX
arn :: Maybe Text
accessConfiguration :: Maybe AccessConfiguration
$sel:httpStatus:DescribeSourceLocationResponse' :: DescribeSourceLocationResponse -> Int
$sel:tags:DescribeSourceLocationResponse' :: DescribeSourceLocationResponse -> Maybe (HashMap Text Text)
$sel:sourceLocationName:DescribeSourceLocationResponse' :: DescribeSourceLocationResponse -> Maybe Text
$sel:segmentDeliveryConfigurations:DescribeSourceLocationResponse' :: DescribeSourceLocationResponse
-> Maybe [SegmentDeliveryConfiguration]
$sel:lastModifiedTime:DescribeSourceLocationResponse' :: DescribeSourceLocationResponse -> Maybe POSIX
$sel:httpConfiguration:DescribeSourceLocationResponse' :: DescribeSourceLocationResponse -> Maybe HttpConfiguration
$sel:defaultSegmentDeliveryConfiguration:DescribeSourceLocationResponse' :: DescribeSourceLocationResponse
-> Maybe DefaultSegmentDeliveryConfiguration
$sel:creationTime:DescribeSourceLocationResponse' :: DescribeSourceLocationResponse -> Maybe POSIX
$sel:arn:DescribeSourceLocationResponse' :: DescribeSourceLocationResponse -> Maybe Text
$sel:accessConfiguration:DescribeSourceLocationResponse' :: DescribeSourceLocationResponse -> Maybe AccessConfiguration
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe AccessConfiguration
accessConfiguration
      seq :: forall a b. a -> b -> b
`Prelude.seq` 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 DefaultSegmentDeliveryConfiguration
defaultSegmentDeliveryConfiguration
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe HttpConfiguration
httpConfiguration
      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 [SegmentDeliveryConfiguration]
segmentDeliveryConfigurations
      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 Int
httpStatus