{-# 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.CreateVodSource
-- 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 VOD source configuration parameters.
module Amazonka.MediaTailor.CreateVodSource
  ( -- * Creating a Request
    CreateVodSource (..),
    newCreateVodSource,

    -- * Request Lenses
    createVodSource_tags,
    createVodSource_httpPackageConfigurations,
    createVodSource_sourceLocationName,
    createVodSource_vodSourceName,

    -- * Destructuring the Response
    CreateVodSourceResponse (..),
    newCreateVodSourceResponse,

    -- * Response Lenses
    createVodSourceResponse_arn,
    createVodSourceResponse_creationTime,
    createVodSourceResponse_httpPackageConfigurations,
    createVodSourceResponse_lastModifiedTime,
    createVodSourceResponse_sourceLocationName,
    createVodSourceResponse_tags,
    createVodSourceResponse_vodSourceName,
    createVodSourceResponse_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:/ 'newCreateVodSource' smart constructor.
data CreateVodSource = CreateVodSource'
  { -- | The tags to assign 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>.
    CreateVodSource -> Maybe (HashMap Text Text)
tags :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | A list of HTTP package configuration parameters for this VOD source.
    CreateVodSource -> [HttpPackageConfiguration]
httpPackageConfigurations :: [HttpPackageConfiguration],
    -- | The name of the source location for this VOD source.
    CreateVodSource -> Text
sourceLocationName :: Prelude.Text,
    -- | The name associated with the VOD source.>
    CreateVodSource -> Text
vodSourceName :: Prelude.Text
  }
  deriving (CreateVodSource -> CreateVodSource -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateVodSource -> CreateVodSource -> Bool
$c/= :: CreateVodSource -> CreateVodSource -> Bool
== :: CreateVodSource -> CreateVodSource -> Bool
$c== :: CreateVodSource -> CreateVodSource -> Bool
Prelude.Eq, ReadPrec [CreateVodSource]
ReadPrec CreateVodSource
Int -> ReadS CreateVodSource
ReadS [CreateVodSource]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateVodSource]
$creadListPrec :: ReadPrec [CreateVodSource]
readPrec :: ReadPrec CreateVodSource
$creadPrec :: ReadPrec CreateVodSource
readList :: ReadS [CreateVodSource]
$creadList :: ReadS [CreateVodSource]
readsPrec :: Int -> ReadS CreateVodSource
$creadsPrec :: Int -> ReadS CreateVodSource
Prelude.Read, Int -> CreateVodSource -> ShowS
[CreateVodSource] -> ShowS
CreateVodSource -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateVodSource] -> ShowS
$cshowList :: [CreateVodSource] -> ShowS
show :: CreateVodSource -> String
$cshow :: CreateVodSource -> String
showsPrec :: Int -> CreateVodSource -> ShowS
$cshowsPrec :: Int -> CreateVodSource -> ShowS
Prelude.Show, forall x. Rep CreateVodSource x -> CreateVodSource
forall x. CreateVodSource -> Rep CreateVodSource x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateVodSource x -> CreateVodSource
$cfrom :: forall x. CreateVodSource -> Rep CreateVodSource x
Prelude.Generic)

-- |
-- Create a value of 'CreateVodSource' 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', 'createVodSource_tags' - The tags to assign 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>.
--
-- 'httpPackageConfigurations', 'createVodSource_httpPackageConfigurations' - A list of HTTP package configuration parameters for this VOD source.
--
-- 'sourceLocationName', 'createVodSource_sourceLocationName' - The name of the source location for this VOD source.
--
-- 'vodSourceName', 'createVodSource_vodSourceName' - The name associated with the VOD source.>
newCreateVodSource ::
  -- | 'sourceLocationName'
  Prelude.Text ->
  -- | 'vodSourceName'
  Prelude.Text ->
  CreateVodSource
newCreateVodSource :: Text -> Text -> CreateVodSource
newCreateVodSource
  Text
pSourceLocationName_
  Text
pVodSourceName_ =
    CreateVodSource'
      { $sel:tags:CreateVodSource' :: Maybe (HashMap Text Text)
tags = forall a. Maybe a
Prelude.Nothing,
        $sel:httpPackageConfigurations:CreateVodSource' :: [HttpPackageConfiguration]
httpPackageConfigurations = forall a. Monoid a => a
Prelude.mempty,
        $sel:sourceLocationName:CreateVodSource' :: Text
sourceLocationName = Text
pSourceLocationName_,
        $sel:vodSourceName:CreateVodSource' :: Text
vodSourceName = Text
pVodSourceName_
      }

-- | The tags to assign 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>.
createVodSource_tags :: Lens.Lens' CreateVodSource (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
createVodSource_tags :: Lens' CreateVodSource (Maybe (HashMap Text Text))
createVodSource_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateVodSource' {Maybe (HashMap Text Text)
tags :: Maybe (HashMap Text Text)
$sel:tags:CreateVodSource' :: CreateVodSource -> Maybe (HashMap Text Text)
tags} -> Maybe (HashMap Text Text)
tags) (\s :: CreateVodSource
s@CreateVodSource' {} Maybe (HashMap Text Text)
a -> CreateVodSource
s {$sel:tags:CreateVodSource' :: Maybe (HashMap Text Text)
tags = Maybe (HashMap Text Text)
a} :: CreateVodSource) 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 VOD source.
createVodSource_httpPackageConfigurations :: Lens.Lens' CreateVodSource [HttpPackageConfiguration]
createVodSource_httpPackageConfigurations :: Lens' CreateVodSource [HttpPackageConfiguration]
createVodSource_httpPackageConfigurations = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateVodSource' {[HttpPackageConfiguration]
httpPackageConfigurations :: [HttpPackageConfiguration]
$sel:httpPackageConfigurations:CreateVodSource' :: CreateVodSource -> [HttpPackageConfiguration]
httpPackageConfigurations} -> [HttpPackageConfiguration]
httpPackageConfigurations) (\s :: CreateVodSource
s@CreateVodSource' {} [HttpPackageConfiguration]
a -> CreateVodSource
s {$sel:httpPackageConfigurations:CreateVodSource' :: [HttpPackageConfiguration]
httpPackageConfigurations = [HttpPackageConfiguration]
a} :: CreateVodSource) 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 source location for this VOD source.
createVodSource_sourceLocationName :: Lens.Lens' CreateVodSource Prelude.Text
createVodSource_sourceLocationName :: Lens' CreateVodSource Text
createVodSource_sourceLocationName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateVodSource' {Text
sourceLocationName :: Text
$sel:sourceLocationName:CreateVodSource' :: CreateVodSource -> Text
sourceLocationName} -> Text
sourceLocationName) (\s :: CreateVodSource
s@CreateVodSource' {} Text
a -> CreateVodSource
s {$sel:sourceLocationName:CreateVodSource' :: Text
sourceLocationName = Text
a} :: CreateVodSource)

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

instance Core.AWSRequest CreateVodSource where
  type
    AWSResponse CreateVodSource =
      CreateVodSourceResponse
  request :: (Service -> Service) -> CreateVodSource -> Request CreateVodSource
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 CreateVodSource
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse CreateVodSource)))
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
-> CreateVodSourceResponse
CreateVodSourceResponse'
            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 CreateVodSource where
  hashWithSalt :: Int -> CreateVodSource -> Int
hashWithSalt Int
_salt CreateVodSource' {[HttpPackageConfiguration]
Maybe (HashMap Text Text)
Text
vodSourceName :: Text
sourceLocationName :: Text
httpPackageConfigurations :: [HttpPackageConfiguration]
tags :: Maybe (HashMap Text Text)
$sel:vodSourceName:CreateVodSource' :: CreateVodSource -> Text
$sel:sourceLocationName:CreateVodSource' :: CreateVodSource -> Text
$sel:httpPackageConfigurations:CreateVodSource' :: CreateVodSource -> [HttpPackageConfiguration]
$sel:tags:CreateVodSource' :: CreateVodSource -> 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
sourceLocationName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
vodSourceName

instance Prelude.NFData CreateVodSource where
  rnf :: CreateVodSource -> ()
rnf CreateVodSource' {[HttpPackageConfiguration]
Maybe (HashMap Text Text)
Text
vodSourceName :: Text
sourceLocationName :: Text
httpPackageConfigurations :: [HttpPackageConfiguration]
tags :: Maybe (HashMap Text Text)
$sel:vodSourceName:CreateVodSource' :: CreateVodSource -> Text
$sel:sourceLocationName:CreateVodSource' :: CreateVodSource -> Text
$sel:httpPackageConfigurations:CreateVodSource' :: CreateVodSource -> [HttpPackageConfiguration]
$sel:tags:CreateVodSource' :: CreateVodSource -> 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
sourceLocationName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
vodSourceName

instance Data.ToHeaders CreateVodSource where
  toHeaders :: CreateVodSource -> 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 CreateVodSource where
  toJSON :: CreateVodSource -> Value
toJSON CreateVodSource' {[HttpPackageConfiguration]
Maybe (HashMap Text Text)
Text
vodSourceName :: Text
sourceLocationName :: Text
httpPackageConfigurations :: [HttpPackageConfiguration]
tags :: Maybe (HashMap Text Text)
$sel:vodSourceName:CreateVodSource' :: CreateVodSource -> Text
$sel:sourceLocationName:CreateVodSource' :: CreateVodSource -> Text
$sel:httpPackageConfigurations:CreateVodSource' :: CreateVodSource -> [HttpPackageConfiguration]
$sel:tags:CreateVodSource' :: CreateVodSource -> 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 CreateVodSource where
  toPath :: CreateVodSource -> ByteString
toPath CreateVodSource' {[HttpPackageConfiguration]
Maybe (HashMap Text Text)
Text
vodSourceName :: Text
sourceLocationName :: Text
httpPackageConfigurations :: [HttpPackageConfiguration]
tags :: Maybe (HashMap Text Text)
$sel:vodSourceName:CreateVodSource' :: CreateVodSource -> Text
$sel:sourceLocationName:CreateVodSource' :: CreateVodSource -> Text
$sel:httpPackageConfigurations:CreateVodSource' :: CreateVodSource -> [HttpPackageConfiguration]
$sel:tags:CreateVodSource' :: CreateVodSource -> 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
"/vodSource/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
vodSourceName
      ]

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

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

-- |
-- Create a value of 'CreateVodSourceResponse' 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', 'createVodSourceResponse_arn' - The ARN to assign to this VOD source.
--
-- 'creationTime', 'createVodSourceResponse_creationTime' - The time the VOD source was created.
--
-- 'httpPackageConfigurations', 'createVodSourceResponse_httpPackageConfigurations' - A list of HTTP package configuration parameters for this VOD source.
--
-- 'lastModifiedTime', 'createVodSourceResponse_lastModifiedTime' - The time the VOD source was last modified.
--
-- 'sourceLocationName', 'createVodSourceResponse_sourceLocationName' - The name to assign to the source location for this VOD source.
--
-- 'tags', 'createVodSourceResponse_tags' - The tags to assign 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', 'createVodSourceResponse_vodSourceName' - The name to assign to the VOD source.
--
-- 'httpStatus', 'createVodSourceResponse_httpStatus' - The response's http status code.
newCreateVodSourceResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  CreateVodSourceResponse
newCreateVodSourceResponse :: Int -> CreateVodSourceResponse
newCreateVodSourceResponse Int
pHttpStatus_ =
  CreateVodSourceResponse'
    { $sel:arn:CreateVodSourceResponse' :: Maybe Text
arn = forall a. Maybe a
Prelude.Nothing,
      $sel:creationTime:CreateVodSourceResponse' :: Maybe POSIX
creationTime = forall a. Maybe a
Prelude.Nothing,
      $sel:httpPackageConfigurations:CreateVodSourceResponse' :: Maybe [HttpPackageConfiguration]
httpPackageConfigurations = forall a. Maybe a
Prelude.Nothing,
      $sel:lastModifiedTime:CreateVodSourceResponse' :: Maybe POSIX
lastModifiedTime = forall a. Maybe a
Prelude.Nothing,
      $sel:sourceLocationName:CreateVodSourceResponse' :: Maybe Text
sourceLocationName = forall a. Maybe a
Prelude.Nothing,
      $sel:tags:CreateVodSourceResponse' :: Maybe (HashMap Text Text)
tags = forall a. Maybe a
Prelude.Nothing,
      $sel:vodSourceName:CreateVodSourceResponse' :: Maybe Text
vodSourceName = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:CreateVodSourceResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The ARN to assign to this VOD source.
createVodSourceResponse_arn :: Lens.Lens' CreateVodSourceResponse (Prelude.Maybe Prelude.Text)
createVodSourceResponse_arn :: Lens' CreateVodSourceResponse (Maybe Text)
createVodSourceResponse_arn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateVodSourceResponse' {Maybe Text
arn :: Maybe Text
$sel:arn:CreateVodSourceResponse' :: CreateVodSourceResponse -> Maybe Text
arn} -> Maybe Text
arn) (\s :: CreateVodSourceResponse
s@CreateVodSourceResponse' {} Maybe Text
a -> CreateVodSourceResponse
s {$sel:arn:CreateVodSourceResponse' :: Maybe Text
arn = Maybe Text
a} :: CreateVodSourceResponse)

-- | The time the VOD source was created.
createVodSourceResponse_creationTime :: Lens.Lens' CreateVodSourceResponse (Prelude.Maybe Prelude.UTCTime)
createVodSourceResponse_creationTime :: Lens' CreateVodSourceResponse (Maybe UTCTime)
createVodSourceResponse_creationTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateVodSourceResponse' {Maybe POSIX
creationTime :: Maybe POSIX
$sel:creationTime:CreateVodSourceResponse' :: CreateVodSourceResponse -> Maybe POSIX
creationTime} -> Maybe POSIX
creationTime) (\s :: CreateVodSourceResponse
s@CreateVodSourceResponse' {} Maybe POSIX
a -> CreateVodSourceResponse
s {$sel:creationTime:CreateVodSourceResponse' :: Maybe POSIX
creationTime = Maybe POSIX
a} :: CreateVodSourceResponse) 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 VOD source.
createVodSourceResponse_httpPackageConfigurations :: Lens.Lens' CreateVodSourceResponse (Prelude.Maybe [HttpPackageConfiguration])
createVodSourceResponse_httpPackageConfigurations :: Lens' CreateVodSourceResponse (Maybe [HttpPackageConfiguration])
createVodSourceResponse_httpPackageConfigurations = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateVodSourceResponse' {Maybe [HttpPackageConfiguration]
httpPackageConfigurations :: Maybe [HttpPackageConfiguration]
$sel:httpPackageConfigurations:CreateVodSourceResponse' :: CreateVodSourceResponse -> Maybe [HttpPackageConfiguration]
httpPackageConfigurations} -> Maybe [HttpPackageConfiguration]
httpPackageConfigurations) (\s :: CreateVodSourceResponse
s@CreateVodSourceResponse' {} Maybe [HttpPackageConfiguration]
a -> CreateVodSourceResponse
s {$sel:httpPackageConfigurations:CreateVodSourceResponse' :: Maybe [HttpPackageConfiguration]
httpPackageConfigurations = Maybe [HttpPackageConfiguration]
a} :: CreateVodSourceResponse) 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 VOD source was last modified.
createVodSourceResponse_lastModifiedTime :: Lens.Lens' CreateVodSourceResponse (Prelude.Maybe Prelude.UTCTime)
createVodSourceResponse_lastModifiedTime :: Lens' CreateVodSourceResponse (Maybe UTCTime)
createVodSourceResponse_lastModifiedTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateVodSourceResponse' {Maybe POSIX
lastModifiedTime :: Maybe POSIX
$sel:lastModifiedTime:CreateVodSourceResponse' :: CreateVodSourceResponse -> Maybe POSIX
lastModifiedTime} -> Maybe POSIX
lastModifiedTime) (\s :: CreateVodSourceResponse
s@CreateVodSourceResponse' {} Maybe POSIX
a -> CreateVodSourceResponse
s {$sel:lastModifiedTime:CreateVodSourceResponse' :: Maybe POSIX
lastModifiedTime = Maybe POSIX
a} :: CreateVodSourceResponse) 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 source location for this VOD source.
createVodSourceResponse_sourceLocationName :: Lens.Lens' CreateVodSourceResponse (Prelude.Maybe Prelude.Text)
createVodSourceResponse_sourceLocationName :: Lens' CreateVodSourceResponse (Maybe Text)
createVodSourceResponse_sourceLocationName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateVodSourceResponse' {Maybe Text
sourceLocationName :: Maybe Text
$sel:sourceLocationName:CreateVodSourceResponse' :: CreateVodSourceResponse -> Maybe Text
sourceLocationName} -> Maybe Text
sourceLocationName) (\s :: CreateVodSourceResponse
s@CreateVodSourceResponse' {} Maybe Text
a -> CreateVodSourceResponse
s {$sel:sourceLocationName:CreateVodSourceResponse' :: Maybe Text
sourceLocationName = Maybe Text
a} :: CreateVodSourceResponse)

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

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

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