{-# 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.CreateSourceLocation
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Creates 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.CreateSourceLocation
  ( -- * Creating a Request
    CreateSourceLocation (..),
    newCreateSourceLocation,

    -- * Request Lenses
    createSourceLocation_accessConfiguration,
    createSourceLocation_defaultSegmentDeliveryConfiguration,
    createSourceLocation_segmentDeliveryConfigurations,
    createSourceLocation_tags,
    createSourceLocation_httpConfiguration,
    createSourceLocation_sourceLocationName,

    -- * Destructuring the Response
    CreateSourceLocationResponse (..),
    newCreateSourceLocationResponse,

    -- * Response Lenses
    createSourceLocationResponse_accessConfiguration,
    createSourceLocationResponse_arn,
    createSourceLocationResponse_creationTime,
    createSourceLocationResponse_defaultSegmentDeliveryConfiguration,
    createSourceLocationResponse_httpConfiguration,
    createSourceLocationResponse_lastModifiedTime,
    createSourceLocationResponse_segmentDeliveryConfigurations,
    createSourceLocationResponse_sourceLocationName,
    createSourceLocationResponse_tags,
    createSourceLocationResponse_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:/ 'newCreateSourceLocation' smart constructor.
data CreateSourceLocation = CreateSourceLocation'
  { -- | Access configuration parameters. Configures the type of authentication
    -- used to access content from your source location.
    CreateSourceLocation -> Maybe AccessConfiguration
accessConfiguration :: Prelude.Maybe AccessConfiguration,
    -- | The optional configuration for the server that serves segments.
    CreateSourceLocation -> Maybe DefaultSegmentDeliveryConfiguration
defaultSegmentDeliveryConfiguration :: Prelude.Maybe DefaultSegmentDeliveryConfiguration,
    -- | A list of the segment delivery configurations associated with this
    -- resource.
    CreateSourceLocation -> Maybe [SegmentDeliveryConfiguration]
segmentDeliveryConfigurations :: Prelude.Maybe [SegmentDeliveryConfiguration],
    -- | The tags to assign 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>.
    CreateSourceLocation -> Maybe (HashMap Text Text)
tags :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | The source\'s HTTP package configurations.
    CreateSourceLocation -> HttpConfiguration
httpConfiguration :: HttpConfiguration,
    -- | The name associated with the source location.
    CreateSourceLocation -> Text
sourceLocationName :: Prelude.Text
  }
  deriving (CreateSourceLocation -> CreateSourceLocation -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateSourceLocation -> CreateSourceLocation -> Bool
$c/= :: CreateSourceLocation -> CreateSourceLocation -> Bool
== :: CreateSourceLocation -> CreateSourceLocation -> Bool
$c== :: CreateSourceLocation -> CreateSourceLocation -> Bool
Prelude.Eq, ReadPrec [CreateSourceLocation]
ReadPrec CreateSourceLocation
Int -> ReadS CreateSourceLocation
ReadS [CreateSourceLocation]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateSourceLocation]
$creadListPrec :: ReadPrec [CreateSourceLocation]
readPrec :: ReadPrec CreateSourceLocation
$creadPrec :: ReadPrec CreateSourceLocation
readList :: ReadS [CreateSourceLocation]
$creadList :: ReadS [CreateSourceLocation]
readsPrec :: Int -> ReadS CreateSourceLocation
$creadsPrec :: Int -> ReadS CreateSourceLocation
Prelude.Read, Int -> CreateSourceLocation -> ShowS
[CreateSourceLocation] -> ShowS
CreateSourceLocation -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateSourceLocation] -> ShowS
$cshowList :: [CreateSourceLocation] -> ShowS
show :: CreateSourceLocation -> String
$cshow :: CreateSourceLocation -> String
showsPrec :: Int -> CreateSourceLocation -> ShowS
$cshowsPrec :: Int -> CreateSourceLocation -> ShowS
Prelude.Show, forall x. Rep CreateSourceLocation x -> CreateSourceLocation
forall x. CreateSourceLocation -> Rep CreateSourceLocation x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateSourceLocation x -> CreateSourceLocation
$cfrom :: forall x. CreateSourceLocation -> Rep CreateSourceLocation x
Prelude.Generic)

-- |
-- Create a value of 'CreateSourceLocation' 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', 'createSourceLocation_accessConfiguration' - Access configuration parameters. Configures the type of authentication
-- used to access content from your source location.
--
-- 'defaultSegmentDeliveryConfiguration', 'createSourceLocation_defaultSegmentDeliveryConfiguration' - The optional configuration for the server that serves segments.
--
-- 'segmentDeliveryConfigurations', 'createSourceLocation_segmentDeliveryConfigurations' - A list of the segment delivery configurations associated with this
-- resource.
--
-- 'tags', 'createSourceLocation_tags' - The tags to assign 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>.
--
-- 'httpConfiguration', 'createSourceLocation_httpConfiguration' - The source\'s HTTP package configurations.
--
-- 'sourceLocationName', 'createSourceLocation_sourceLocationName' - The name associated with the source location.
newCreateSourceLocation ::
  -- | 'httpConfiguration'
  HttpConfiguration ->
  -- | 'sourceLocationName'
  Prelude.Text ->
  CreateSourceLocation
newCreateSourceLocation :: HttpConfiguration -> Text -> CreateSourceLocation
newCreateSourceLocation
  HttpConfiguration
pHttpConfiguration_
  Text
pSourceLocationName_ =
    CreateSourceLocation'
      { $sel:accessConfiguration:CreateSourceLocation' :: Maybe AccessConfiguration
accessConfiguration =
          forall a. Maybe a
Prelude.Nothing,
        $sel:defaultSegmentDeliveryConfiguration:CreateSourceLocation' :: Maybe DefaultSegmentDeliveryConfiguration
defaultSegmentDeliveryConfiguration =
          forall a. Maybe a
Prelude.Nothing,
        $sel:segmentDeliveryConfigurations:CreateSourceLocation' :: Maybe [SegmentDeliveryConfiguration]
segmentDeliveryConfigurations = forall a. Maybe a
Prelude.Nothing,
        $sel:tags:CreateSourceLocation' :: Maybe (HashMap Text Text)
tags = forall a. Maybe a
Prelude.Nothing,
        $sel:httpConfiguration:CreateSourceLocation' :: HttpConfiguration
httpConfiguration = HttpConfiguration
pHttpConfiguration_,
        $sel:sourceLocationName:CreateSourceLocation' :: Text
sourceLocationName = Text
pSourceLocationName_
      }

-- | Access configuration parameters. Configures the type of authentication
-- used to access content from your source location.
createSourceLocation_accessConfiguration :: Lens.Lens' CreateSourceLocation (Prelude.Maybe AccessConfiguration)
createSourceLocation_accessConfiguration :: Lens' CreateSourceLocation (Maybe AccessConfiguration)
createSourceLocation_accessConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateSourceLocation' {Maybe AccessConfiguration
accessConfiguration :: Maybe AccessConfiguration
$sel:accessConfiguration:CreateSourceLocation' :: CreateSourceLocation -> Maybe AccessConfiguration
accessConfiguration} -> Maybe AccessConfiguration
accessConfiguration) (\s :: CreateSourceLocation
s@CreateSourceLocation' {} Maybe AccessConfiguration
a -> CreateSourceLocation
s {$sel:accessConfiguration:CreateSourceLocation' :: Maybe AccessConfiguration
accessConfiguration = Maybe AccessConfiguration
a} :: CreateSourceLocation)

-- | The optional configuration for the server that serves segments.
createSourceLocation_defaultSegmentDeliveryConfiguration :: Lens.Lens' CreateSourceLocation (Prelude.Maybe DefaultSegmentDeliveryConfiguration)
createSourceLocation_defaultSegmentDeliveryConfiguration :: Lens'
  CreateSourceLocation (Maybe DefaultSegmentDeliveryConfiguration)
createSourceLocation_defaultSegmentDeliveryConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateSourceLocation' {Maybe DefaultSegmentDeliveryConfiguration
defaultSegmentDeliveryConfiguration :: Maybe DefaultSegmentDeliveryConfiguration
$sel:defaultSegmentDeliveryConfiguration:CreateSourceLocation' :: CreateSourceLocation -> Maybe DefaultSegmentDeliveryConfiguration
defaultSegmentDeliveryConfiguration} -> Maybe DefaultSegmentDeliveryConfiguration
defaultSegmentDeliveryConfiguration) (\s :: CreateSourceLocation
s@CreateSourceLocation' {} Maybe DefaultSegmentDeliveryConfiguration
a -> CreateSourceLocation
s {$sel:defaultSegmentDeliveryConfiguration:CreateSourceLocation' :: Maybe DefaultSegmentDeliveryConfiguration
defaultSegmentDeliveryConfiguration = Maybe DefaultSegmentDeliveryConfiguration
a} :: CreateSourceLocation)

-- | A list of the segment delivery configurations associated with this
-- resource.
createSourceLocation_segmentDeliveryConfigurations :: Lens.Lens' CreateSourceLocation (Prelude.Maybe [SegmentDeliveryConfiguration])
createSourceLocation_segmentDeliveryConfigurations :: Lens' CreateSourceLocation (Maybe [SegmentDeliveryConfiguration])
createSourceLocation_segmentDeliveryConfigurations = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateSourceLocation' {Maybe [SegmentDeliveryConfiguration]
segmentDeliveryConfigurations :: Maybe [SegmentDeliveryConfiguration]
$sel:segmentDeliveryConfigurations:CreateSourceLocation' :: CreateSourceLocation -> Maybe [SegmentDeliveryConfiguration]
segmentDeliveryConfigurations} -> Maybe [SegmentDeliveryConfiguration]
segmentDeliveryConfigurations) (\s :: CreateSourceLocation
s@CreateSourceLocation' {} Maybe [SegmentDeliveryConfiguration]
a -> CreateSourceLocation
s {$sel:segmentDeliveryConfigurations:CreateSourceLocation' :: Maybe [SegmentDeliveryConfiguration]
segmentDeliveryConfigurations = Maybe [SegmentDeliveryConfiguration]
a} :: CreateSourceLocation) 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 tags to assign 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>.
createSourceLocation_tags :: Lens.Lens' CreateSourceLocation (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
createSourceLocation_tags :: Lens' CreateSourceLocation (Maybe (HashMap Text Text))
createSourceLocation_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateSourceLocation' {Maybe (HashMap Text Text)
tags :: Maybe (HashMap Text Text)
$sel:tags:CreateSourceLocation' :: CreateSourceLocation -> Maybe (HashMap Text Text)
tags} -> Maybe (HashMap Text Text)
tags) (\s :: CreateSourceLocation
s@CreateSourceLocation' {} Maybe (HashMap Text Text)
a -> CreateSourceLocation
s {$sel:tags:CreateSourceLocation' :: Maybe (HashMap Text Text)
tags = Maybe (HashMap Text Text)
a} :: CreateSourceLocation) 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 source\'s HTTP package configurations.
createSourceLocation_httpConfiguration :: Lens.Lens' CreateSourceLocation HttpConfiguration
createSourceLocation_httpConfiguration :: Lens' CreateSourceLocation HttpConfiguration
createSourceLocation_httpConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateSourceLocation' {HttpConfiguration
httpConfiguration :: HttpConfiguration
$sel:httpConfiguration:CreateSourceLocation' :: CreateSourceLocation -> HttpConfiguration
httpConfiguration} -> HttpConfiguration
httpConfiguration) (\s :: CreateSourceLocation
s@CreateSourceLocation' {} HttpConfiguration
a -> CreateSourceLocation
s {$sel:httpConfiguration:CreateSourceLocation' :: HttpConfiguration
httpConfiguration = HttpConfiguration
a} :: CreateSourceLocation)

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

instance Core.AWSRequest CreateSourceLocation where
  type
    AWSResponse CreateSourceLocation =
      CreateSourceLocationResponse
  request :: (Service -> Service)
-> CreateSourceLocation -> Request CreateSourceLocation
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 CreateSourceLocation
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse CreateSourceLocation)))
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
-> CreateSourceLocationResponse
CreateSourceLocationResponse'
            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 CreateSourceLocation where
  hashWithSalt :: Int -> CreateSourceLocation -> Int
hashWithSalt Int
_salt CreateSourceLocation' {Maybe [SegmentDeliveryConfiguration]
Maybe (HashMap Text Text)
Maybe DefaultSegmentDeliveryConfiguration
Maybe AccessConfiguration
Text
HttpConfiguration
sourceLocationName :: Text
httpConfiguration :: HttpConfiguration
tags :: Maybe (HashMap Text Text)
segmentDeliveryConfigurations :: Maybe [SegmentDeliveryConfiguration]
defaultSegmentDeliveryConfiguration :: Maybe DefaultSegmentDeliveryConfiguration
accessConfiguration :: Maybe AccessConfiguration
$sel:sourceLocationName:CreateSourceLocation' :: CreateSourceLocation -> Text
$sel:httpConfiguration:CreateSourceLocation' :: CreateSourceLocation -> HttpConfiguration
$sel:tags:CreateSourceLocation' :: CreateSourceLocation -> Maybe (HashMap Text Text)
$sel:segmentDeliveryConfigurations:CreateSourceLocation' :: CreateSourceLocation -> Maybe [SegmentDeliveryConfiguration]
$sel:defaultSegmentDeliveryConfiguration:CreateSourceLocation' :: CreateSourceLocation -> Maybe DefaultSegmentDeliveryConfiguration
$sel:accessConfiguration:CreateSourceLocation' :: CreateSourceLocation -> Maybe AccessConfiguration
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe AccessConfiguration
accessConfiguration
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe DefaultSegmentDeliveryConfiguration
defaultSegmentDeliveryConfiguration
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [SegmentDeliveryConfiguration]
segmentDeliveryConfigurations
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (HashMap Text Text)
tags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` HttpConfiguration
httpConfiguration
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
sourceLocationName

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

instance Data.ToHeaders CreateSourceLocation where
  toHeaders :: CreateSourceLocation -> 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 CreateSourceLocation where
  toJSON :: CreateSourceLocation -> Value
toJSON CreateSourceLocation' {Maybe [SegmentDeliveryConfiguration]
Maybe (HashMap Text Text)
Maybe DefaultSegmentDeliveryConfiguration
Maybe AccessConfiguration
Text
HttpConfiguration
sourceLocationName :: Text
httpConfiguration :: HttpConfiguration
tags :: Maybe (HashMap Text Text)
segmentDeliveryConfigurations :: Maybe [SegmentDeliveryConfiguration]
defaultSegmentDeliveryConfiguration :: Maybe DefaultSegmentDeliveryConfiguration
accessConfiguration :: Maybe AccessConfiguration
$sel:sourceLocationName:CreateSourceLocation' :: CreateSourceLocation -> Text
$sel:httpConfiguration:CreateSourceLocation' :: CreateSourceLocation -> HttpConfiguration
$sel:tags:CreateSourceLocation' :: CreateSourceLocation -> Maybe (HashMap Text Text)
$sel:segmentDeliveryConfigurations:CreateSourceLocation' :: CreateSourceLocation -> Maybe [SegmentDeliveryConfiguration]
$sel:defaultSegmentDeliveryConfiguration:CreateSourceLocation' :: CreateSourceLocation -> Maybe DefaultSegmentDeliveryConfiguration
$sel:accessConfiguration:CreateSourceLocation' :: CreateSourceLocation -> Maybe AccessConfiguration
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"AccessConfiguration" 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 AccessConfiguration
accessConfiguration,
            (Key
"DefaultSegmentDeliveryConfiguration" 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 DefaultSegmentDeliveryConfiguration
defaultSegmentDeliveryConfiguration,
            (Key
"SegmentDeliveryConfigurations" 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 [SegmentDeliveryConfiguration]
segmentDeliveryConfigurations,
            (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
"HttpConfiguration" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= HttpConfiguration
httpConfiguration)
          ]
      )

instance Data.ToPath CreateSourceLocation where
  toPath :: CreateSourceLocation -> ByteString
toPath CreateSourceLocation' {Maybe [SegmentDeliveryConfiguration]
Maybe (HashMap Text Text)
Maybe DefaultSegmentDeliveryConfiguration
Maybe AccessConfiguration
Text
HttpConfiguration
sourceLocationName :: Text
httpConfiguration :: HttpConfiguration
tags :: Maybe (HashMap Text Text)
segmentDeliveryConfigurations :: Maybe [SegmentDeliveryConfiguration]
defaultSegmentDeliveryConfiguration :: Maybe DefaultSegmentDeliveryConfiguration
accessConfiguration :: Maybe AccessConfiguration
$sel:sourceLocationName:CreateSourceLocation' :: CreateSourceLocation -> Text
$sel:httpConfiguration:CreateSourceLocation' :: CreateSourceLocation -> HttpConfiguration
$sel:tags:CreateSourceLocation' :: CreateSourceLocation -> Maybe (HashMap Text Text)
$sel:segmentDeliveryConfigurations:CreateSourceLocation' :: CreateSourceLocation -> Maybe [SegmentDeliveryConfiguration]
$sel:defaultSegmentDeliveryConfiguration:CreateSourceLocation' :: CreateSourceLocation -> Maybe DefaultSegmentDeliveryConfiguration
$sel:accessConfiguration:CreateSourceLocation' :: CreateSourceLocation -> Maybe AccessConfiguration
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ByteString
"/sourceLocation/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
sourceLocationName]

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

-- | /See:/ 'newCreateSourceLocationResponse' smart constructor.
data CreateSourceLocationResponse = CreateSourceLocationResponse'
  { -- | Access configuration parameters. Configures the type of authentication
    -- used to access content from your source location.
    CreateSourceLocationResponse -> Maybe AccessConfiguration
accessConfiguration :: Prelude.Maybe AccessConfiguration,
    -- | The ARN to assign to the source location.
    CreateSourceLocationResponse -> Maybe Text
arn :: Prelude.Maybe Prelude.Text,
    -- | The time the source location was created.
    CreateSourceLocationResponse -> Maybe POSIX
creationTime :: Prelude.Maybe Data.POSIX,
    -- | The optional configuration for the server that serves segments.
    CreateSourceLocationResponse
-> Maybe DefaultSegmentDeliveryConfiguration
defaultSegmentDeliveryConfiguration :: Prelude.Maybe DefaultSegmentDeliveryConfiguration,
    -- | The source\'s HTTP package configurations.
    CreateSourceLocationResponse -> Maybe HttpConfiguration
httpConfiguration :: Prelude.Maybe HttpConfiguration,
    -- | The time the source location was last modified.
    CreateSourceLocationResponse -> Maybe POSIX
lastModifiedTime :: Prelude.Maybe Data.POSIX,
    -- | The segment delivery configurations for the source location. For
    -- information about MediaTailor configurations, see
    -- <https://docs.aws.amazon.com/mediatailor/latest/ug/configurations.html Working with configurations in AWS Elemental MediaTailor>.
    CreateSourceLocationResponse
-> Maybe [SegmentDeliveryConfiguration]
segmentDeliveryConfigurations :: Prelude.Maybe [SegmentDeliveryConfiguration],
    -- | The name to assign to the source location.
    CreateSourceLocationResponse -> Maybe Text
sourceLocationName :: Prelude.Maybe Prelude.Text,
    -- | The tags to assign 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>.
    CreateSourceLocationResponse -> Maybe (HashMap Text Text)
tags :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | The response's http status code.
    CreateSourceLocationResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (CreateSourceLocationResponse
-> CreateSourceLocationResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateSourceLocationResponse
-> CreateSourceLocationResponse -> Bool
$c/= :: CreateSourceLocationResponse
-> CreateSourceLocationResponse -> Bool
== :: CreateSourceLocationResponse
-> CreateSourceLocationResponse -> Bool
$c== :: CreateSourceLocationResponse
-> CreateSourceLocationResponse -> Bool
Prelude.Eq, ReadPrec [CreateSourceLocationResponse]
ReadPrec CreateSourceLocationResponse
Int -> ReadS CreateSourceLocationResponse
ReadS [CreateSourceLocationResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateSourceLocationResponse]
$creadListPrec :: ReadPrec [CreateSourceLocationResponse]
readPrec :: ReadPrec CreateSourceLocationResponse
$creadPrec :: ReadPrec CreateSourceLocationResponse
readList :: ReadS [CreateSourceLocationResponse]
$creadList :: ReadS [CreateSourceLocationResponse]
readsPrec :: Int -> ReadS CreateSourceLocationResponse
$creadsPrec :: Int -> ReadS CreateSourceLocationResponse
Prelude.Read, Int -> CreateSourceLocationResponse -> ShowS
[CreateSourceLocationResponse] -> ShowS
CreateSourceLocationResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateSourceLocationResponse] -> ShowS
$cshowList :: [CreateSourceLocationResponse] -> ShowS
show :: CreateSourceLocationResponse -> String
$cshow :: CreateSourceLocationResponse -> String
showsPrec :: Int -> CreateSourceLocationResponse -> ShowS
$cshowsPrec :: Int -> CreateSourceLocationResponse -> ShowS
Prelude.Show, forall x.
Rep CreateSourceLocationResponse x -> CreateSourceLocationResponse
forall x.
CreateSourceLocationResponse -> Rep CreateSourceLocationResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CreateSourceLocationResponse x -> CreateSourceLocationResponse
$cfrom :: forall x.
CreateSourceLocationResponse -> Rep CreateSourceLocationResponse x
Prelude.Generic)

-- |
-- Create a value of 'CreateSourceLocationResponse' 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', 'createSourceLocationResponse_accessConfiguration' - Access configuration parameters. Configures the type of authentication
-- used to access content from your source location.
--
-- 'arn', 'createSourceLocationResponse_arn' - The ARN to assign to the source location.
--
-- 'creationTime', 'createSourceLocationResponse_creationTime' - The time the source location was created.
--
-- 'defaultSegmentDeliveryConfiguration', 'createSourceLocationResponse_defaultSegmentDeliveryConfiguration' - The optional configuration for the server that serves segments.
--
-- 'httpConfiguration', 'createSourceLocationResponse_httpConfiguration' - The source\'s HTTP package configurations.
--
-- 'lastModifiedTime', 'createSourceLocationResponse_lastModifiedTime' - The time the source location was last modified.
--
-- 'segmentDeliveryConfigurations', 'createSourceLocationResponse_segmentDeliveryConfigurations' - The segment delivery configurations for the source location. For
-- information about MediaTailor configurations, see
-- <https://docs.aws.amazon.com/mediatailor/latest/ug/configurations.html Working with configurations in AWS Elemental MediaTailor>.
--
-- 'sourceLocationName', 'createSourceLocationResponse_sourceLocationName' - The name to assign to the source location.
--
-- 'tags', 'createSourceLocationResponse_tags' - The tags to assign 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', 'createSourceLocationResponse_httpStatus' - The response's http status code.
newCreateSourceLocationResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  CreateSourceLocationResponse
newCreateSourceLocationResponse :: Int -> CreateSourceLocationResponse
newCreateSourceLocationResponse Int
pHttpStatus_ =
  CreateSourceLocationResponse'
    { $sel:accessConfiguration:CreateSourceLocationResponse' :: Maybe AccessConfiguration
accessConfiguration =
        forall a. Maybe a
Prelude.Nothing,
      $sel:arn:CreateSourceLocationResponse' :: Maybe Text
arn = forall a. Maybe a
Prelude.Nothing,
      $sel:creationTime:CreateSourceLocationResponse' :: Maybe POSIX
creationTime = forall a. Maybe a
Prelude.Nothing,
      $sel:defaultSegmentDeliveryConfiguration:CreateSourceLocationResponse' :: Maybe DefaultSegmentDeliveryConfiguration
defaultSegmentDeliveryConfiguration =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpConfiguration:CreateSourceLocationResponse' :: Maybe HttpConfiguration
httpConfiguration = forall a. Maybe a
Prelude.Nothing,
      $sel:lastModifiedTime:CreateSourceLocationResponse' :: Maybe POSIX
lastModifiedTime = forall a. Maybe a
Prelude.Nothing,
      $sel:segmentDeliveryConfigurations:CreateSourceLocationResponse' :: Maybe [SegmentDeliveryConfiguration]
segmentDeliveryConfigurations =
        forall a. Maybe a
Prelude.Nothing,
      $sel:sourceLocationName:CreateSourceLocationResponse' :: Maybe Text
sourceLocationName = forall a. Maybe a
Prelude.Nothing,
      $sel:tags:CreateSourceLocationResponse' :: Maybe (HashMap Text Text)
tags = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:CreateSourceLocationResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Access configuration parameters. Configures the type of authentication
-- used to access content from your source location.
createSourceLocationResponse_accessConfiguration :: Lens.Lens' CreateSourceLocationResponse (Prelude.Maybe AccessConfiguration)
createSourceLocationResponse_accessConfiguration :: Lens' CreateSourceLocationResponse (Maybe AccessConfiguration)
createSourceLocationResponse_accessConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateSourceLocationResponse' {Maybe AccessConfiguration
accessConfiguration :: Maybe AccessConfiguration
$sel:accessConfiguration:CreateSourceLocationResponse' :: CreateSourceLocationResponse -> Maybe AccessConfiguration
accessConfiguration} -> Maybe AccessConfiguration
accessConfiguration) (\s :: CreateSourceLocationResponse
s@CreateSourceLocationResponse' {} Maybe AccessConfiguration
a -> CreateSourceLocationResponse
s {$sel:accessConfiguration:CreateSourceLocationResponse' :: Maybe AccessConfiguration
accessConfiguration = Maybe AccessConfiguration
a} :: CreateSourceLocationResponse)

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

-- | The time the source location was created.
createSourceLocationResponse_creationTime :: Lens.Lens' CreateSourceLocationResponse (Prelude.Maybe Prelude.UTCTime)
createSourceLocationResponse_creationTime :: Lens' CreateSourceLocationResponse (Maybe UTCTime)
createSourceLocationResponse_creationTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateSourceLocationResponse' {Maybe POSIX
creationTime :: Maybe POSIX
$sel:creationTime:CreateSourceLocationResponse' :: CreateSourceLocationResponse -> Maybe POSIX
creationTime} -> Maybe POSIX
creationTime) (\s :: CreateSourceLocationResponse
s@CreateSourceLocationResponse' {} Maybe POSIX
a -> CreateSourceLocationResponse
s {$sel:creationTime:CreateSourceLocationResponse' :: Maybe POSIX
creationTime = Maybe POSIX
a} :: CreateSourceLocationResponse) 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 optional configuration for the server that serves segments.
createSourceLocationResponse_defaultSegmentDeliveryConfiguration :: Lens.Lens' CreateSourceLocationResponse (Prelude.Maybe DefaultSegmentDeliveryConfiguration)
createSourceLocationResponse_defaultSegmentDeliveryConfiguration :: Lens'
  CreateSourceLocationResponse
  (Maybe DefaultSegmentDeliveryConfiguration)
createSourceLocationResponse_defaultSegmentDeliveryConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateSourceLocationResponse' {Maybe DefaultSegmentDeliveryConfiguration
defaultSegmentDeliveryConfiguration :: Maybe DefaultSegmentDeliveryConfiguration
$sel:defaultSegmentDeliveryConfiguration:CreateSourceLocationResponse' :: CreateSourceLocationResponse
-> Maybe DefaultSegmentDeliveryConfiguration
defaultSegmentDeliveryConfiguration} -> Maybe DefaultSegmentDeliveryConfiguration
defaultSegmentDeliveryConfiguration) (\s :: CreateSourceLocationResponse
s@CreateSourceLocationResponse' {} Maybe DefaultSegmentDeliveryConfiguration
a -> CreateSourceLocationResponse
s {$sel:defaultSegmentDeliveryConfiguration:CreateSourceLocationResponse' :: Maybe DefaultSegmentDeliveryConfiguration
defaultSegmentDeliveryConfiguration = Maybe DefaultSegmentDeliveryConfiguration
a} :: CreateSourceLocationResponse)

-- | The source\'s HTTP package configurations.
createSourceLocationResponse_httpConfiguration :: Lens.Lens' CreateSourceLocationResponse (Prelude.Maybe HttpConfiguration)
createSourceLocationResponse_httpConfiguration :: Lens' CreateSourceLocationResponse (Maybe HttpConfiguration)
createSourceLocationResponse_httpConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateSourceLocationResponse' {Maybe HttpConfiguration
httpConfiguration :: Maybe HttpConfiguration
$sel:httpConfiguration:CreateSourceLocationResponse' :: CreateSourceLocationResponse -> Maybe HttpConfiguration
httpConfiguration} -> Maybe HttpConfiguration
httpConfiguration) (\s :: CreateSourceLocationResponse
s@CreateSourceLocationResponse' {} Maybe HttpConfiguration
a -> CreateSourceLocationResponse
s {$sel:httpConfiguration:CreateSourceLocationResponse' :: Maybe HttpConfiguration
httpConfiguration = Maybe HttpConfiguration
a} :: CreateSourceLocationResponse)

-- | The time the source location was last modified.
createSourceLocationResponse_lastModifiedTime :: Lens.Lens' CreateSourceLocationResponse (Prelude.Maybe Prelude.UTCTime)
createSourceLocationResponse_lastModifiedTime :: Lens' CreateSourceLocationResponse (Maybe UTCTime)
createSourceLocationResponse_lastModifiedTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateSourceLocationResponse' {Maybe POSIX
lastModifiedTime :: Maybe POSIX
$sel:lastModifiedTime:CreateSourceLocationResponse' :: CreateSourceLocationResponse -> Maybe POSIX
lastModifiedTime} -> Maybe POSIX
lastModifiedTime) (\s :: CreateSourceLocationResponse
s@CreateSourceLocationResponse' {} Maybe POSIX
a -> CreateSourceLocationResponse
s {$sel:lastModifiedTime:CreateSourceLocationResponse' :: Maybe POSIX
lastModifiedTime = Maybe POSIX
a} :: CreateSourceLocationResponse) 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 segment delivery configurations for the source location. For
-- information about MediaTailor configurations, see
-- <https://docs.aws.amazon.com/mediatailor/latest/ug/configurations.html Working with configurations in AWS Elemental MediaTailor>.
createSourceLocationResponse_segmentDeliveryConfigurations :: Lens.Lens' CreateSourceLocationResponse (Prelude.Maybe [SegmentDeliveryConfiguration])
createSourceLocationResponse_segmentDeliveryConfigurations :: Lens'
  CreateSourceLocationResponse (Maybe [SegmentDeliveryConfiguration])
createSourceLocationResponse_segmentDeliveryConfigurations = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateSourceLocationResponse' {Maybe [SegmentDeliveryConfiguration]
segmentDeliveryConfigurations :: Maybe [SegmentDeliveryConfiguration]
$sel:segmentDeliveryConfigurations:CreateSourceLocationResponse' :: CreateSourceLocationResponse
-> Maybe [SegmentDeliveryConfiguration]
segmentDeliveryConfigurations} -> Maybe [SegmentDeliveryConfiguration]
segmentDeliveryConfigurations) (\s :: CreateSourceLocationResponse
s@CreateSourceLocationResponse' {} Maybe [SegmentDeliveryConfiguration]
a -> CreateSourceLocationResponse
s {$sel:segmentDeliveryConfigurations:CreateSourceLocationResponse' :: Maybe [SegmentDeliveryConfiguration]
segmentDeliveryConfigurations = Maybe [SegmentDeliveryConfiguration]
a} :: CreateSourceLocationResponse) 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 source location.
createSourceLocationResponse_sourceLocationName :: Lens.Lens' CreateSourceLocationResponse (Prelude.Maybe Prelude.Text)
createSourceLocationResponse_sourceLocationName :: Lens' CreateSourceLocationResponse (Maybe Text)
createSourceLocationResponse_sourceLocationName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateSourceLocationResponse' {Maybe Text
sourceLocationName :: Maybe Text
$sel:sourceLocationName:CreateSourceLocationResponse' :: CreateSourceLocationResponse -> Maybe Text
sourceLocationName} -> Maybe Text
sourceLocationName) (\s :: CreateSourceLocationResponse
s@CreateSourceLocationResponse' {} Maybe Text
a -> CreateSourceLocationResponse
s {$sel:sourceLocationName:CreateSourceLocationResponse' :: Maybe Text
sourceLocationName = Maybe Text
a} :: CreateSourceLocationResponse)

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

instance Prelude.NFData CreateSourceLocationResponse where
  rnf :: CreateSourceLocationResponse -> ()
rnf CreateSourceLocationResponse' {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:CreateSourceLocationResponse' :: CreateSourceLocationResponse -> Int
$sel:tags:CreateSourceLocationResponse' :: CreateSourceLocationResponse -> Maybe (HashMap Text Text)
$sel:sourceLocationName:CreateSourceLocationResponse' :: CreateSourceLocationResponse -> Maybe Text
$sel:segmentDeliveryConfigurations:CreateSourceLocationResponse' :: CreateSourceLocationResponse
-> Maybe [SegmentDeliveryConfiguration]
$sel:lastModifiedTime:CreateSourceLocationResponse' :: CreateSourceLocationResponse -> Maybe POSIX
$sel:httpConfiguration:CreateSourceLocationResponse' :: CreateSourceLocationResponse -> Maybe HttpConfiguration
$sel:defaultSegmentDeliveryConfiguration:CreateSourceLocationResponse' :: CreateSourceLocationResponse
-> Maybe DefaultSegmentDeliveryConfiguration
$sel:creationTime:CreateSourceLocationResponse' :: CreateSourceLocationResponse -> Maybe POSIX
$sel:arn:CreateSourceLocationResponse' :: CreateSourceLocationResponse -> Maybe Text
$sel:accessConfiguration:CreateSourceLocationResponse' :: CreateSourceLocationResponse -> 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