{-# 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.CreateLiveSource
-- 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 configuration.
module Amazonka.MediaTailor.CreateLiveSource
  ( -- * Creating a Request
    CreateLiveSource (..),
    newCreateLiveSource,

    -- * Request Lenses
    createLiveSource_tags,
    createLiveSource_httpPackageConfigurations,
    createLiveSource_liveSourceName,
    createLiveSource_sourceLocationName,

    -- * Destructuring the Response
    CreateLiveSourceResponse (..),
    newCreateLiveSourceResponse,

    -- * Response Lenses
    createLiveSourceResponse_arn,
    createLiveSourceResponse_creationTime,
    createLiveSourceResponse_httpPackageConfigurations,
    createLiveSourceResponse_lastModifiedTime,
    createLiveSourceResponse_liveSourceName,
    createLiveSourceResponse_sourceLocationName,
    createLiveSourceResponse_tags,
    createLiveSourceResponse_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:/ 'newCreateLiveSource' smart constructor.
data CreateLiveSource = CreateLiveSource'
  { -- | The tags to assign to the live 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>.
    CreateLiveSource -> Maybe (HashMap Text Text)
tags :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | A list of HTTP package configuration parameters for this live source.
    CreateLiveSource -> [HttpPackageConfiguration]
httpPackageConfigurations :: [HttpPackageConfiguration],
    -- | The name of the live source.
    CreateLiveSource -> Text
liveSourceName :: Prelude.Text,
    -- | The name of the source location.
    CreateLiveSource -> Text
sourceLocationName :: Prelude.Text
  }
  deriving (CreateLiveSource -> CreateLiveSource -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateLiveSource -> CreateLiveSource -> Bool
$c/= :: CreateLiveSource -> CreateLiveSource -> Bool
== :: CreateLiveSource -> CreateLiveSource -> Bool
$c== :: CreateLiveSource -> CreateLiveSource -> Bool
Prelude.Eq, ReadPrec [CreateLiveSource]
ReadPrec CreateLiveSource
Int -> ReadS CreateLiveSource
ReadS [CreateLiveSource]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateLiveSource]
$creadListPrec :: ReadPrec [CreateLiveSource]
readPrec :: ReadPrec CreateLiveSource
$creadPrec :: ReadPrec CreateLiveSource
readList :: ReadS [CreateLiveSource]
$creadList :: ReadS [CreateLiveSource]
readsPrec :: Int -> ReadS CreateLiveSource
$creadsPrec :: Int -> ReadS CreateLiveSource
Prelude.Read, Int -> CreateLiveSource -> ShowS
[CreateLiveSource] -> ShowS
CreateLiveSource -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateLiveSource] -> ShowS
$cshowList :: [CreateLiveSource] -> ShowS
show :: CreateLiveSource -> String
$cshow :: CreateLiveSource -> String
showsPrec :: Int -> CreateLiveSource -> ShowS
$cshowsPrec :: Int -> CreateLiveSource -> ShowS
Prelude.Show, forall x. Rep CreateLiveSource x -> CreateLiveSource
forall x. CreateLiveSource -> Rep CreateLiveSource x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateLiveSource x -> CreateLiveSource
$cfrom :: forall x. CreateLiveSource -> Rep CreateLiveSource x
Prelude.Generic)

-- |
-- Create a value of 'CreateLiveSource' 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:
--
-- 'tags', 'createLiveSource_tags' - The tags to assign to the live 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>.
--
-- 'httpPackageConfigurations', 'createLiveSource_httpPackageConfigurations' - A list of HTTP package configuration parameters for this live source.
--
-- 'liveSourceName', 'createLiveSource_liveSourceName' - The name of the live source.
--
-- 'sourceLocationName', 'createLiveSource_sourceLocationName' - The name of the source location.
newCreateLiveSource ::
  -- | 'liveSourceName'
  Prelude.Text ->
  -- | 'sourceLocationName'
  Prelude.Text ->
  CreateLiveSource
newCreateLiveSource :: Text -> Text -> CreateLiveSource
newCreateLiveSource
  Text
pLiveSourceName_
  Text
pSourceLocationName_ =
    CreateLiveSource'
      { $sel:tags:CreateLiveSource' :: Maybe (HashMap Text Text)
tags = forall a. Maybe a
Prelude.Nothing,
        $sel:httpPackageConfigurations:CreateLiveSource' :: [HttpPackageConfiguration]
httpPackageConfigurations = forall a. Monoid a => a
Prelude.mempty,
        $sel:liveSourceName:CreateLiveSource' :: Text
liveSourceName = Text
pLiveSourceName_,
        $sel:sourceLocationName:CreateLiveSource' :: Text
sourceLocationName = Text
pSourceLocationName_
      }

-- | The tags to assign to the live 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>.
createLiveSource_tags :: Lens.Lens' CreateLiveSource (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
createLiveSource_tags :: Lens' CreateLiveSource (Maybe (HashMap Text Text))
createLiveSource_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateLiveSource' {Maybe (HashMap Text Text)
tags :: Maybe (HashMap Text Text)
$sel:tags:CreateLiveSource' :: CreateLiveSource -> Maybe (HashMap Text Text)
tags} -> Maybe (HashMap Text Text)
tags) (\s :: CreateLiveSource
s@CreateLiveSource' {} Maybe (HashMap Text Text)
a -> CreateLiveSource
s {$sel:tags:CreateLiveSource' :: Maybe (HashMap Text Text)
tags = Maybe (HashMap Text Text)
a} :: CreateLiveSource) 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

-- | A list of HTTP package configuration parameters for this live source.
createLiveSource_httpPackageConfigurations :: Lens.Lens' CreateLiveSource [HttpPackageConfiguration]
createLiveSource_httpPackageConfigurations :: Lens' CreateLiveSource [HttpPackageConfiguration]
createLiveSource_httpPackageConfigurations = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateLiveSource' {[HttpPackageConfiguration]
httpPackageConfigurations :: [HttpPackageConfiguration]
$sel:httpPackageConfigurations:CreateLiveSource' :: CreateLiveSource -> [HttpPackageConfiguration]
httpPackageConfigurations} -> [HttpPackageConfiguration]
httpPackageConfigurations) (\s :: CreateLiveSource
s@CreateLiveSource' {} [HttpPackageConfiguration]
a -> CreateLiveSource
s {$sel:httpPackageConfigurations:CreateLiveSource' :: [HttpPackageConfiguration]
httpPackageConfigurations = [HttpPackageConfiguration]
a} :: CreateLiveSource) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

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

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

instance Core.AWSRequest CreateLiveSource where
  type
    AWSResponse CreateLiveSource =
      CreateLiveSourceResponse
  request :: (Service -> Service)
-> CreateLiveSource -> Request CreateLiveSource
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.postJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy CreateLiveSource
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse CreateLiveSource)))
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 Text
-> Maybe (HashMap Text Text)
-> Int
-> CreateLiveSourceResponse
CreateLiveSourceResponse'
            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
"LiveSourceName")
            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 CreateLiveSource where
  hashWithSalt :: Int -> CreateLiveSource -> Int
hashWithSalt Int
_salt CreateLiveSource' {[HttpPackageConfiguration]
Maybe (HashMap Text Text)
Text
sourceLocationName :: Text
liveSourceName :: Text
httpPackageConfigurations :: [HttpPackageConfiguration]
tags :: Maybe (HashMap Text Text)
$sel:sourceLocationName:CreateLiveSource' :: CreateLiveSource -> Text
$sel:liveSourceName:CreateLiveSource' :: CreateLiveSource -> Text
$sel:httpPackageConfigurations:CreateLiveSource' :: CreateLiveSource -> [HttpPackageConfiguration]
$sel:tags:CreateLiveSource' :: CreateLiveSource -> Maybe (HashMap Text Text)
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (HashMap Text Text)
tags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` [HttpPackageConfiguration]
httpPackageConfigurations
      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 CreateLiveSource where
  rnf :: CreateLiveSource -> ()
rnf CreateLiveSource' {[HttpPackageConfiguration]
Maybe (HashMap Text Text)
Text
sourceLocationName :: Text
liveSourceName :: Text
httpPackageConfigurations :: [HttpPackageConfiguration]
tags :: Maybe (HashMap Text Text)
$sel:sourceLocationName:CreateLiveSource' :: CreateLiveSource -> Text
$sel:liveSourceName:CreateLiveSource' :: CreateLiveSource -> Text
$sel:httpPackageConfigurations:CreateLiveSource' :: CreateLiveSource -> [HttpPackageConfiguration]
$sel:tags:CreateLiveSource' :: CreateLiveSource -> Maybe (HashMap Text Text)
..} =
    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 [HttpPackageConfiguration]
httpPackageConfigurations
      seq :: forall a b. a -> b -> b
`Prelude.seq` 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 CreateLiveSource where
  toHeaders :: CreateLiveSource -> 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.ToJSON CreateLiveSource where
  toJSON :: CreateLiveSource -> Value
toJSON CreateLiveSource' {[HttpPackageConfiguration]
Maybe (HashMap Text Text)
Text
sourceLocationName :: Text
liveSourceName :: Text
httpPackageConfigurations :: [HttpPackageConfiguration]
tags :: Maybe (HashMap Text Text)
$sel:sourceLocationName:CreateLiveSource' :: CreateLiveSource -> Text
$sel:liveSourceName:CreateLiveSource' :: CreateLiveSource -> Text
$sel:httpPackageConfigurations:CreateLiveSource' :: CreateLiveSource -> [HttpPackageConfiguration]
$sel:tags:CreateLiveSource' :: CreateLiveSource -> Maybe (HashMap Text Text)
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"tags" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (HashMap Text Text)
tags,
            forall a. a -> Maybe a
Prelude.Just
              ( Key
"HttpPackageConfigurations"
                  forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= [HttpPackageConfiguration]
httpPackageConfigurations
              )
          ]
      )

instance Data.ToPath CreateLiveSource where
  toPath :: CreateLiveSource -> ByteString
toPath CreateLiveSource' {[HttpPackageConfiguration]
Maybe (HashMap Text Text)
Text
sourceLocationName :: Text
liveSourceName :: Text
httpPackageConfigurations :: [HttpPackageConfiguration]
tags :: Maybe (HashMap Text Text)
$sel:sourceLocationName:CreateLiveSource' :: CreateLiveSource -> Text
$sel:liveSourceName:CreateLiveSource' :: CreateLiveSource -> Text
$sel:httpPackageConfigurations:CreateLiveSource' :: CreateLiveSource -> [HttpPackageConfiguration]
$sel:tags:CreateLiveSource' :: CreateLiveSource -> Maybe (HashMap Text 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 CreateLiveSource where
  toQuery :: CreateLiveSource -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

-- | /See:/ 'newCreateLiveSourceResponse' smart constructor.
data CreateLiveSourceResponse = CreateLiveSourceResponse'
  { -- | The ARN to assign to the live source.
    CreateLiveSourceResponse -> Maybe Text
arn :: Prelude.Maybe Prelude.Text,
    -- | The time the live source was created.
    CreateLiveSourceResponse -> Maybe POSIX
creationTime :: Prelude.Maybe Data.POSIX,
    -- | A list of HTTP package configuration parameters for this live source.
    CreateLiveSourceResponse -> Maybe [HttpPackageConfiguration]
httpPackageConfigurations :: Prelude.Maybe [HttpPackageConfiguration],
    -- | The time the live source was last modified.
    CreateLiveSourceResponse -> Maybe POSIX
lastModifiedTime :: Prelude.Maybe Data.POSIX,
    -- | The name to assign to the live source.
    CreateLiveSourceResponse -> Maybe Text
liveSourceName :: Prelude.Maybe Prelude.Text,
    -- | The name to assign to the source location of the live source.
    CreateLiveSourceResponse -> Maybe Text
sourceLocationName :: Prelude.Maybe Prelude.Text,
    -- | The tags to assign to the live 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>.
    CreateLiveSourceResponse -> Maybe (HashMap Text Text)
tags :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | The response's http status code.
    CreateLiveSourceResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (CreateLiveSourceResponse -> CreateLiveSourceResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateLiveSourceResponse -> CreateLiveSourceResponse -> Bool
$c/= :: CreateLiveSourceResponse -> CreateLiveSourceResponse -> Bool
== :: CreateLiveSourceResponse -> CreateLiveSourceResponse -> Bool
$c== :: CreateLiveSourceResponse -> CreateLiveSourceResponse -> Bool
Prelude.Eq, ReadPrec [CreateLiveSourceResponse]
ReadPrec CreateLiveSourceResponse
Int -> ReadS CreateLiveSourceResponse
ReadS [CreateLiveSourceResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateLiveSourceResponse]
$creadListPrec :: ReadPrec [CreateLiveSourceResponse]
readPrec :: ReadPrec CreateLiveSourceResponse
$creadPrec :: ReadPrec CreateLiveSourceResponse
readList :: ReadS [CreateLiveSourceResponse]
$creadList :: ReadS [CreateLiveSourceResponse]
readsPrec :: Int -> ReadS CreateLiveSourceResponse
$creadsPrec :: Int -> ReadS CreateLiveSourceResponse
Prelude.Read, Int -> CreateLiveSourceResponse -> ShowS
[CreateLiveSourceResponse] -> ShowS
CreateLiveSourceResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateLiveSourceResponse] -> ShowS
$cshowList :: [CreateLiveSourceResponse] -> ShowS
show :: CreateLiveSourceResponse -> String
$cshow :: CreateLiveSourceResponse -> String
showsPrec :: Int -> CreateLiveSourceResponse -> ShowS
$cshowsPrec :: Int -> CreateLiveSourceResponse -> ShowS
Prelude.Show, forall x.
Rep CreateLiveSourceResponse x -> CreateLiveSourceResponse
forall x.
CreateLiveSourceResponse -> Rep CreateLiveSourceResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CreateLiveSourceResponse x -> CreateLiveSourceResponse
$cfrom :: forall x.
CreateLiveSourceResponse -> Rep CreateLiveSourceResponse x
Prelude.Generic)

-- |
-- Create a value of 'CreateLiveSourceResponse' 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', 'createLiveSourceResponse_arn' - The ARN to assign to the live source.
--
-- 'creationTime', 'createLiveSourceResponse_creationTime' - The time the live source was created.
--
-- 'httpPackageConfigurations', 'createLiveSourceResponse_httpPackageConfigurations' - A list of HTTP package configuration parameters for this live source.
--
-- 'lastModifiedTime', 'createLiveSourceResponse_lastModifiedTime' - The time the live source was last modified.
--
-- 'liveSourceName', 'createLiveSourceResponse_liveSourceName' - The name to assign to the live source.
--
-- 'sourceLocationName', 'createLiveSourceResponse_sourceLocationName' - The name to assign to the source location of the live source.
--
-- 'tags', 'createLiveSourceResponse_tags' - The tags to assign to the live 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>.
--
-- 'httpStatus', 'createLiveSourceResponse_httpStatus' - The response's http status code.
newCreateLiveSourceResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  CreateLiveSourceResponse
newCreateLiveSourceResponse :: Int -> CreateLiveSourceResponse
newCreateLiveSourceResponse Int
pHttpStatus_ =
  CreateLiveSourceResponse'
    { $sel:arn:CreateLiveSourceResponse' :: Maybe Text
arn = forall a. Maybe a
Prelude.Nothing,
      $sel:creationTime:CreateLiveSourceResponse' :: Maybe POSIX
creationTime = forall a. Maybe a
Prelude.Nothing,
      $sel:httpPackageConfigurations:CreateLiveSourceResponse' :: Maybe [HttpPackageConfiguration]
httpPackageConfigurations = forall a. Maybe a
Prelude.Nothing,
      $sel:lastModifiedTime:CreateLiveSourceResponse' :: Maybe POSIX
lastModifiedTime = forall a. Maybe a
Prelude.Nothing,
      $sel:liveSourceName:CreateLiveSourceResponse' :: Maybe Text
liveSourceName = forall a. Maybe a
Prelude.Nothing,
      $sel:sourceLocationName:CreateLiveSourceResponse' :: Maybe Text
sourceLocationName = forall a. Maybe a
Prelude.Nothing,
      $sel:tags:CreateLiveSourceResponse' :: Maybe (HashMap Text Text)
tags = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:CreateLiveSourceResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The ARN to assign to the live source.
createLiveSourceResponse_arn :: Lens.Lens' CreateLiveSourceResponse (Prelude.Maybe Prelude.Text)
createLiveSourceResponse_arn :: Lens' CreateLiveSourceResponse (Maybe Text)
createLiveSourceResponse_arn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateLiveSourceResponse' {Maybe Text
arn :: Maybe Text
$sel:arn:CreateLiveSourceResponse' :: CreateLiveSourceResponse -> Maybe Text
arn} -> Maybe Text
arn) (\s :: CreateLiveSourceResponse
s@CreateLiveSourceResponse' {} Maybe Text
a -> CreateLiveSourceResponse
s {$sel:arn:CreateLiveSourceResponse' :: Maybe Text
arn = Maybe Text
a} :: CreateLiveSourceResponse)

-- | The time the live source was created.
createLiveSourceResponse_creationTime :: Lens.Lens' CreateLiveSourceResponse (Prelude.Maybe Prelude.UTCTime)
createLiveSourceResponse_creationTime :: Lens' CreateLiveSourceResponse (Maybe UTCTime)
createLiveSourceResponse_creationTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateLiveSourceResponse' {Maybe POSIX
creationTime :: Maybe POSIX
$sel:creationTime:CreateLiveSourceResponse' :: CreateLiveSourceResponse -> Maybe POSIX
creationTime} -> Maybe POSIX
creationTime) (\s :: CreateLiveSourceResponse
s@CreateLiveSourceResponse' {} Maybe POSIX
a -> CreateLiveSourceResponse
s {$sel:creationTime:CreateLiveSourceResponse' :: Maybe POSIX
creationTime = Maybe POSIX
a} :: CreateLiveSourceResponse) 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 HTTP package configuration parameters for this live source.
createLiveSourceResponse_httpPackageConfigurations :: Lens.Lens' CreateLiveSourceResponse (Prelude.Maybe [HttpPackageConfiguration])
createLiveSourceResponse_httpPackageConfigurations :: Lens' CreateLiveSourceResponse (Maybe [HttpPackageConfiguration])
createLiveSourceResponse_httpPackageConfigurations = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateLiveSourceResponse' {Maybe [HttpPackageConfiguration]
httpPackageConfigurations :: Maybe [HttpPackageConfiguration]
$sel:httpPackageConfigurations:CreateLiveSourceResponse' :: CreateLiveSourceResponse -> Maybe [HttpPackageConfiguration]
httpPackageConfigurations} -> Maybe [HttpPackageConfiguration]
httpPackageConfigurations) (\s :: CreateLiveSourceResponse
s@CreateLiveSourceResponse' {} Maybe [HttpPackageConfiguration]
a -> CreateLiveSourceResponse
s {$sel:httpPackageConfigurations:CreateLiveSourceResponse' :: Maybe [HttpPackageConfiguration]
httpPackageConfigurations = Maybe [HttpPackageConfiguration]
a} :: CreateLiveSourceResponse) 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 time the live source was last modified.
createLiveSourceResponse_lastModifiedTime :: Lens.Lens' CreateLiveSourceResponse (Prelude.Maybe Prelude.UTCTime)
createLiveSourceResponse_lastModifiedTime :: Lens' CreateLiveSourceResponse (Maybe UTCTime)
createLiveSourceResponse_lastModifiedTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateLiveSourceResponse' {Maybe POSIX
lastModifiedTime :: Maybe POSIX
$sel:lastModifiedTime:CreateLiveSourceResponse' :: CreateLiveSourceResponse -> Maybe POSIX
lastModifiedTime} -> Maybe POSIX
lastModifiedTime) (\s :: CreateLiveSourceResponse
s@CreateLiveSourceResponse' {} Maybe POSIX
a -> CreateLiveSourceResponse
s {$sel:lastModifiedTime:CreateLiveSourceResponse' :: Maybe POSIX
lastModifiedTime = Maybe POSIX
a} :: CreateLiveSourceResponse) 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 to assign to the live source.
createLiveSourceResponse_liveSourceName :: Lens.Lens' CreateLiveSourceResponse (Prelude.Maybe Prelude.Text)
createLiveSourceResponse_liveSourceName :: Lens' CreateLiveSourceResponse (Maybe Text)
createLiveSourceResponse_liveSourceName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateLiveSourceResponse' {Maybe Text
liveSourceName :: Maybe Text
$sel:liveSourceName:CreateLiveSourceResponse' :: CreateLiveSourceResponse -> Maybe Text
liveSourceName} -> Maybe Text
liveSourceName) (\s :: CreateLiveSourceResponse
s@CreateLiveSourceResponse' {} Maybe Text
a -> CreateLiveSourceResponse
s {$sel:liveSourceName:CreateLiveSourceResponse' :: Maybe Text
liveSourceName = Maybe Text
a} :: CreateLiveSourceResponse)

-- | The name to assign to the source location of the live source.
createLiveSourceResponse_sourceLocationName :: Lens.Lens' CreateLiveSourceResponse (Prelude.Maybe Prelude.Text)
createLiveSourceResponse_sourceLocationName :: Lens' CreateLiveSourceResponse (Maybe Text)
createLiveSourceResponse_sourceLocationName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateLiveSourceResponse' {Maybe Text
sourceLocationName :: Maybe Text
$sel:sourceLocationName:CreateLiveSourceResponse' :: CreateLiveSourceResponse -> Maybe Text
sourceLocationName} -> Maybe Text
sourceLocationName) (\s :: CreateLiveSourceResponse
s@CreateLiveSourceResponse' {} Maybe Text
a -> CreateLiveSourceResponse
s {$sel:sourceLocationName:CreateLiveSourceResponse' :: Maybe Text
sourceLocationName = Maybe Text
a} :: CreateLiveSourceResponse)

-- | The tags to assign to the live 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>.
createLiveSourceResponse_tags :: Lens.Lens' CreateLiveSourceResponse (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
createLiveSourceResponse_tags :: Lens' CreateLiveSourceResponse (Maybe (HashMap Text Text))
createLiveSourceResponse_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateLiveSourceResponse' {Maybe (HashMap Text Text)
tags :: Maybe (HashMap Text Text)
$sel:tags:CreateLiveSourceResponse' :: CreateLiveSourceResponse -> Maybe (HashMap Text Text)
tags} -> Maybe (HashMap Text Text)
tags) (\s :: CreateLiveSourceResponse
s@CreateLiveSourceResponse' {} Maybe (HashMap Text Text)
a -> CreateLiveSourceResponse
s {$sel:tags:CreateLiveSourceResponse' :: Maybe (HashMap Text Text)
tags = Maybe (HashMap Text Text)
a} :: CreateLiveSourceResponse) 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.
createLiveSourceResponse_httpStatus :: Lens.Lens' CreateLiveSourceResponse Prelude.Int
createLiveSourceResponse_httpStatus :: Lens' CreateLiveSourceResponse Int
createLiveSourceResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateLiveSourceResponse' {Int
httpStatus :: Int
$sel:httpStatus:CreateLiveSourceResponse' :: CreateLiveSourceResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: CreateLiveSourceResponse
s@CreateLiveSourceResponse' {} Int
a -> CreateLiveSourceResponse
s {$sel:httpStatus:CreateLiveSourceResponse' :: Int
httpStatus = Int
a} :: CreateLiveSourceResponse)

instance Prelude.NFData CreateLiveSourceResponse where
  rnf :: CreateLiveSourceResponse -> ()
rnf CreateLiveSourceResponse' {Int
Maybe [HttpPackageConfiguration]
Maybe Text
Maybe (HashMap Text Text)
Maybe POSIX
httpStatus :: Int
tags :: Maybe (HashMap Text Text)
sourceLocationName :: Maybe Text
liveSourceName :: Maybe Text
lastModifiedTime :: Maybe POSIX
httpPackageConfigurations :: Maybe [HttpPackageConfiguration]
creationTime :: Maybe POSIX
arn :: Maybe Text
$sel:httpStatus:CreateLiveSourceResponse' :: CreateLiveSourceResponse -> Int
$sel:tags:CreateLiveSourceResponse' :: CreateLiveSourceResponse -> Maybe (HashMap Text Text)
$sel:sourceLocationName:CreateLiveSourceResponse' :: CreateLiveSourceResponse -> Maybe Text
$sel:liveSourceName:CreateLiveSourceResponse' :: CreateLiveSourceResponse -> Maybe Text
$sel:lastModifiedTime:CreateLiveSourceResponse' :: CreateLiveSourceResponse -> Maybe POSIX
$sel:httpPackageConfigurations:CreateLiveSourceResponse' :: CreateLiveSourceResponse -> Maybe [HttpPackageConfiguration]
$sel:creationTime:CreateLiveSourceResponse' :: CreateLiveSourceResponse -> Maybe POSIX
$sel:arn:CreateLiveSourceResponse' :: CreateLiveSourceResponse -> 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
liveSourceName
      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