{-# 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.Lightsail.CreateDistribution
-- 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 an Amazon Lightsail content delivery network (CDN) distribution.
--
-- A distribution is a globally distributed network of caching servers that
-- improve the performance of your website or web application hosted on a
-- Lightsail instance. For more information, see
-- <https://lightsail.aws.amazon.com/ls/docs/en_us/articles/amazon-lightsail-content-delivery-network-distributions Content delivery networks in Amazon Lightsail>.
module Amazonka.Lightsail.CreateDistribution
  ( -- * Creating a Request
    CreateDistribution (..),
    newCreateDistribution,

    -- * Request Lenses
    createDistribution_cacheBehaviorSettings,
    createDistribution_cacheBehaviors,
    createDistribution_ipAddressType,
    createDistribution_tags,
    createDistribution_distributionName,
    createDistribution_origin,
    createDistribution_defaultCacheBehavior,
    createDistribution_bundleId,

    -- * Destructuring the Response
    CreateDistributionResponse (..),
    newCreateDistributionResponse,

    -- * Response Lenses
    createDistributionResponse_distribution,
    createDistributionResponse_operation,
    createDistributionResponse_httpStatus,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.Lightsail.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newCreateDistribution' smart constructor.
data CreateDistribution = CreateDistribution'
  { -- | An object that describes the cache behavior settings for the
    -- distribution.
    CreateDistribution -> Maybe CacheSettings
cacheBehaviorSettings :: Prelude.Maybe CacheSettings,
    -- | An array of objects that describe the per-path cache behavior for the
    -- distribution.
    CreateDistribution -> Maybe [CacheBehaviorPerPath]
cacheBehaviors :: Prelude.Maybe [CacheBehaviorPerPath],
    -- | The IP address type for the distribution.
    --
    -- The possible values are @ipv4@ for IPv4 only, and @dualstack@ for IPv4
    -- and IPv6.
    --
    -- The default value is @dualstack@.
    CreateDistribution -> Maybe IpAddressType
ipAddressType :: Prelude.Maybe IpAddressType,
    -- | The tag keys and optional values to add to the distribution during
    -- create.
    --
    -- Use the @TagResource@ action to tag a resource after it\'s created.
    CreateDistribution -> Maybe [Tag]
tags :: Prelude.Maybe [Tag],
    -- | The name for the distribution.
    CreateDistribution -> Text
distributionName :: Prelude.Text,
    -- | An object that describes the origin resource for the distribution, such
    -- as a Lightsail instance, bucket, or load balancer.
    --
    -- The distribution pulls, caches, and serves content from the origin.
    CreateDistribution -> InputOrigin
origin :: InputOrigin,
    -- | An object that describes the default cache behavior for the
    -- distribution.
    CreateDistribution -> CacheBehavior
defaultCacheBehavior :: CacheBehavior,
    -- | The bundle ID to use for the distribution.
    --
    -- A distribution bundle describes the specifications of your distribution,
    -- such as the monthly cost and monthly network transfer quota.
    --
    -- Use the @GetDistributionBundles@ action to get a list of distribution
    -- bundle IDs that you can specify.
    CreateDistribution -> Text
bundleId :: Prelude.Text
  }
  deriving (CreateDistribution -> CreateDistribution -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateDistribution -> CreateDistribution -> Bool
$c/= :: CreateDistribution -> CreateDistribution -> Bool
== :: CreateDistribution -> CreateDistribution -> Bool
$c== :: CreateDistribution -> CreateDistribution -> Bool
Prelude.Eq, ReadPrec [CreateDistribution]
ReadPrec CreateDistribution
Int -> ReadS CreateDistribution
ReadS [CreateDistribution]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateDistribution]
$creadListPrec :: ReadPrec [CreateDistribution]
readPrec :: ReadPrec CreateDistribution
$creadPrec :: ReadPrec CreateDistribution
readList :: ReadS [CreateDistribution]
$creadList :: ReadS [CreateDistribution]
readsPrec :: Int -> ReadS CreateDistribution
$creadsPrec :: Int -> ReadS CreateDistribution
Prelude.Read, Int -> CreateDistribution -> ShowS
[CreateDistribution] -> ShowS
CreateDistribution -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateDistribution] -> ShowS
$cshowList :: [CreateDistribution] -> ShowS
show :: CreateDistribution -> String
$cshow :: CreateDistribution -> String
showsPrec :: Int -> CreateDistribution -> ShowS
$cshowsPrec :: Int -> CreateDistribution -> ShowS
Prelude.Show, forall x. Rep CreateDistribution x -> CreateDistribution
forall x. CreateDistribution -> Rep CreateDistribution x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateDistribution x -> CreateDistribution
$cfrom :: forall x. CreateDistribution -> Rep CreateDistribution x
Prelude.Generic)

-- |
-- Create a value of 'CreateDistribution' 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:
--
-- 'cacheBehaviorSettings', 'createDistribution_cacheBehaviorSettings' - An object that describes the cache behavior settings for the
-- distribution.
--
-- 'cacheBehaviors', 'createDistribution_cacheBehaviors' - An array of objects that describe the per-path cache behavior for the
-- distribution.
--
-- 'ipAddressType', 'createDistribution_ipAddressType' - The IP address type for the distribution.
--
-- The possible values are @ipv4@ for IPv4 only, and @dualstack@ for IPv4
-- and IPv6.
--
-- The default value is @dualstack@.
--
-- 'tags', 'createDistribution_tags' - The tag keys and optional values to add to the distribution during
-- create.
--
-- Use the @TagResource@ action to tag a resource after it\'s created.
--
-- 'distributionName', 'createDistribution_distributionName' - The name for the distribution.
--
-- 'origin', 'createDistribution_origin' - An object that describes the origin resource for the distribution, such
-- as a Lightsail instance, bucket, or load balancer.
--
-- The distribution pulls, caches, and serves content from the origin.
--
-- 'defaultCacheBehavior', 'createDistribution_defaultCacheBehavior' - An object that describes the default cache behavior for the
-- distribution.
--
-- 'bundleId', 'createDistribution_bundleId' - The bundle ID to use for the distribution.
--
-- A distribution bundle describes the specifications of your distribution,
-- such as the monthly cost and monthly network transfer quota.
--
-- Use the @GetDistributionBundles@ action to get a list of distribution
-- bundle IDs that you can specify.
newCreateDistribution ::
  -- | 'distributionName'
  Prelude.Text ->
  -- | 'origin'
  InputOrigin ->
  -- | 'defaultCacheBehavior'
  CacheBehavior ->
  -- | 'bundleId'
  Prelude.Text ->
  CreateDistribution
newCreateDistribution :: Text -> InputOrigin -> CacheBehavior -> Text -> CreateDistribution
newCreateDistribution
  Text
pDistributionName_
  InputOrigin
pOrigin_
  CacheBehavior
pDefaultCacheBehavior_
  Text
pBundleId_ =
    CreateDistribution'
      { $sel:cacheBehaviorSettings:CreateDistribution' :: Maybe CacheSettings
cacheBehaviorSettings =
          forall a. Maybe a
Prelude.Nothing,
        $sel:cacheBehaviors:CreateDistribution' :: Maybe [CacheBehaviorPerPath]
cacheBehaviors = forall a. Maybe a
Prelude.Nothing,
        $sel:ipAddressType:CreateDistribution' :: Maybe IpAddressType
ipAddressType = forall a. Maybe a
Prelude.Nothing,
        $sel:tags:CreateDistribution' :: Maybe [Tag]
tags = forall a. Maybe a
Prelude.Nothing,
        $sel:distributionName:CreateDistribution' :: Text
distributionName = Text
pDistributionName_,
        $sel:origin:CreateDistribution' :: InputOrigin
origin = InputOrigin
pOrigin_,
        $sel:defaultCacheBehavior:CreateDistribution' :: CacheBehavior
defaultCacheBehavior = CacheBehavior
pDefaultCacheBehavior_,
        $sel:bundleId:CreateDistribution' :: Text
bundleId = Text
pBundleId_
      }

-- | An object that describes the cache behavior settings for the
-- distribution.
createDistribution_cacheBehaviorSettings :: Lens.Lens' CreateDistribution (Prelude.Maybe CacheSettings)
createDistribution_cacheBehaviorSettings :: Lens' CreateDistribution (Maybe CacheSettings)
createDistribution_cacheBehaviorSettings = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateDistribution' {Maybe CacheSettings
cacheBehaviorSettings :: Maybe CacheSettings
$sel:cacheBehaviorSettings:CreateDistribution' :: CreateDistribution -> Maybe CacheSettings
cacheBehaviorSettings} -> Maybe CacheSettings
cacheBehaviorSettings) (\s :: CreateDistribution
s@CreateDistribution' {} Maybe CacheSettings
a -> CreateDistribution
s {$sel:cacheBehaviorSettings:CreateDistribution' :: Maybe CacheSettings
cacheBehaviorSettings = Maybe CacheSettings
a} :: CreateDistribution)

-- | An array of objects that describe the per-path cache behavior for the
-- distribution.
createDistribution_cacheBehaviors :: Lens.Lens' CreateDistribution (Prelude.Maybe [CacheBehaviorPerPath])
createDistribution_cacheBehaviors :: Lens' CreateDistribution (Maybe [CacheBehaviorPerPath])
createDistribution_cacheBehaviors = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateDistribution' {Maybe [CacheBehaviorPerPath]
cacheBehaviors :: Maybe [CacheBehaviorPerPath]
$sel:cacheBehaviors:CreateDistribution' :: CreateDistribution -> Maybe [CacheBehaviorPerPath]
cacheBehaviors} -> Maybe [CacheBehaviorPerPath]
cacheBehaviors) (\s :: CreateDistribution
s@CreateDistribution' {} Maybe [CacheBehaviorPerPath]
a -> CreateDistribution
s {$sel:cacheBehaviors:CreateDistribution' :: Maybe [CacheBehaviorPerPath]
cacheBehaviors = Maybe [CacheBehaviorPerPath]
a} :: CreateDistribution) 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 IP address type for the distribution.
--
-- The possible values are @ipv4@ for IPv4 only, and @dualstack@ for IPv4
-- and IPv6.
--
-- The default value is @dualstack@.
createDistribution_ipAddressType :: Lens.Lens' CreateDistribution (Prelude.Maybe IpAddressType)
createDistribution_ipAddressType :: Lens' CreateDistribution (Maybe IpAddressType)
createDistribution_ipAddressType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateDistribution' {Maybe IpAddressType
ipAddressType :: Maybe IpAddressType
$sel:ipAddressType:CreateDistribution' :: CreateDistribution -> Maybe IpAddressType
ipAddressType} -> Maybe IpAddressType
ipAddressType) (\s :: CreateDistribution
s@CreateDistribution' {} Maybe IpAddressType
a -> CreateDistribution
s {$sel:ipAddressType:CreateDistribution' :: Maybe IpAddressType
ipAddressType = Maybe IpAddressType
a} :: CreateDistribution)

-- | The tag keys and optional values to add to the distribution during
-- create.
--
-- Use the @TagResource@ action to tag a resource after it\'s created.
createDistribution_tags :: Lens.Lens' CreateDistribution (Prelude.Maybe [Tag])
createDistribution_tags :: Lens' CreateDistribution (Maybe [Tag])
createDistribution_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateDistribution' {Maybe [Tag]
tags :: Maybe [Tag]
$sel:tags:CreateDistribution' :: CreateDistribution -> Maybe [Tag]
tags} -> Maybe [Tag]
tags) (\s :: CreateDistribution
s@CreateDistribution' {} Maybe [Tag]
a -> CreateDistribution
s {$sel:tags:CreateDistribution' :: Maybe [Tag]
tags = Maybe [Tag]
a} :: CreateDistribution) 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 for the distribution.
createDistribution_distributionName :: Lens.Lens' CreateDistribution Prelude.Text
createDistribution_distributionName :: Lens' CreateDistribution Text
createDistribution_distributionName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateDistribution' {Text
distributionName :: Text
$sel:distributionName:CreateDistribution' :: CreateDistribution -> Text
distributionName} -> Text
distributionName) (\s :: CreateDistribution
s@CreateDistribution' {} Text
a -> CreateDistribution
s {$sel:distributionName:CreateDistribution' :: Text
distributionName = Text
a} :: CreateDistribution)

-- | An object that describes the origin resource for the distribution, such
-- as a Lightsail instance, bucket, or load balancer.
--
-- The distribution pulls, caches, and serves content from the origin.
createDistribution_origin :: Lens.Lens' CreateDistribution InputOrigin
createDistribution_origin :: Lens' CreateDistribution InputOrigin
createDistribution_origin = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateDistribution' {InputOrigin
origin :: InputOrigin
$sel:origin:CreateDistribution' :: CreateDistribution -> InputOrigin
origin} -> InputOrigin
origin) (\s :: CreateDistribution
s@CreateDistribution' {} InputOrigin
a -> CreateDistribution
s {$sel:origin:CreateDistribution' :: InputOrigin
origin = InputOrigin
a} :: CreateDistribution)

-- | An object that describes the default cache behavior for the
-- distribution.
createDistribution_defaultCacheBehavior :: Lens.Lens' CreateDistribution CacheBehavior
createDistribution_defaultCacheBehavior :: Lens' CreateDistribution CacheBehavior
createDistribution_defaultCacheBehavior = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateDistribution' {CacheBehavior
defaultCacheBehavior :: CacheBehavior
$sel:defaultCacheBehavior:CreateDistribution' :: CreateDistribution -> CacheBehavior
defaultCacheBehavior} -> CacheBehavior
defaultCacheBehavior) (\s :: CreateDistribution
s@CreateDistribution' {} CacheBehavior
a -> CreateDistribution
s {$sel:defaultCacheBehavior:CreateDistribution' :: CacheBehavior
defaultCacheBehavior = CacheBehavior
a} :: CreateDistribution)

-- | The bundle ID to use for the distribution.
--
-- A distribution bundle describes the specifications of your distribution,
-- such as the monthly cost and monthly network transfer quota.
--
-- Use the @GetDistributionBundles@ action to get a list of distribution
-- bundle IDs that you can specify.
createDistribution_bundleId :: Lens.Lens' CreateDistribution Prelude.Text
createDistribution_bundleId :: Lens' CreateDistribution Text
createDistribution_bundleId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateDistribution' {Text
bundleId :: Text
$sel:bundleId:CreateDistribution' :: CreateDistribution -> Text
bundleId} -> Text
bundleId) (\s :: CreateDistribution
s@CreateDistribution' {} Text
a -> CreateDistribution
s {$sel:bundleId:CreateDistribution' :: Text
bundleId = Text
a} :: CreateDistribution)

instance Core.AWSRequest CreateDistribution where
  type
    AWSResponse CreateDistribution =
      CreateDistributionResponse
  request :: (Service -> Service)
-> CreateDistribution -> Request CreateDistribution
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 CreateDistribution
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse CreateDistribution)))
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 LightsailDistribution
-> Maybe Operation -> Int -> CreateDistributionResponse
CreateDistributionResponse'
            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
"distribution")
            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
"operation")
            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 CreateDistribution where
  hashWithSalt :: Int -> CreateDistribution -> Int
hashWithSalt Int
_salt CreateDistribution' {Maybe [CacheBehaviorPerPath]
Maybe [Tag]
Maybe IpAddressType
Maybe CacheSettings
Text
CacheBehavior
InputOrigin
bundleId :: Text
defaultCacheBehavior :: CacheBehavior
origin :: InputOrigin
distributionName :: Text
tags :: Maybe [Tag]
ipAddressType :: Maybe IpAddressType
cacheBehaviors :: Maybe [CacheBehaviorPerPath]
cacheBehaviorSettings :: Maybe CacheSettings
$sel:bundleId:CreateDistribution' :: CreateDistribution -> Text
$sel:defaultCacheBehavior:CreateDistribution' :: CreateDistribution -> CacheBehavior
$sel:origin:CreateDistribution' :: CreateDistribution -> InputOrigin
$sel:distributionName:CreateDistribution' :: CreateDistribution -> Text
$sel:tags:CreateDistribution' :: CreateDistribution -> Maybe [Tag]
$sel:ipAddressType:CreateDistribution' :: CreateDistribution -> Maybe IpAddressType
$sel:cacheBehaviors:CreateDistribution' :: CreateDistribution -> Maybe [CacheBehaviorPerPath]
$sel:cacheBehaviorSettings:CreateDistribution' :: CreateDistribution -> Maybe CacheSettings
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe CacheSettings
cacheBehaviorSettings
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [CacheBehaviorPerPath]
cacheBehaviors
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe IpAddressType
ipAddressType
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Tag]
tags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
distributionName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` InputOrigin
origin
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` CacheBehavior
defaultCacheBehavior
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
bundleId

instance Prelude.NFData CreateDistribution where
  rnf :: CreateDistribution -> ()
rnf CreateDistribution' {Maybe [CacheBehaviorPerPath]
Maybe [Tag]
Maybe IpAddressType
Maybe CacheSettings
Text
CacheBehavior
InputOrigin
bundleId :: Text
defaultCacheBehavior :: CacheBehavior
origin :: InputOrigin
distributionName :: Text
tags :: Maybe [Tag]
ipAddressType :: Maybe IpAddressType
cacheBehaviors :: Maybe [CacheBehaviorPerPath]
cacheBehaviorSettings :: Maybe CacheSettings
$sel:bundleId:CreateDistribution' :: CreateDistribution -> Text
$sel:defaultCacheBehavior:CreateDistribution' :: CreateDistribution -> CacheBehavior
$sel:origin:CreateDistribution' :: CreateDistribution -> InputOrigin
$sel:distributionName:CreateDistribution' :: CreateDistribution -> Text
$sel:tags:CreateDistribution' :: CreateDistribution -> Maybe [Tag]
$sel:ipAddressType:CreateDistribution' :: CreateDistribution -> Maybe IpAddressType
$sel:cacheBehaviors:CreateDistribution' :: CreateDistribution -> Maybe [CacheBehaviorPerPath]
$sel:cacheBehaviorSettings:CreateDistribution' :: CreateDistribution -> Maybe CacheSettings
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe CacheSettings
cacheBehaviorSettings
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [CacheBehaviorPerPath]
cacheBehaviors
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe IpAddressType
ipAddressType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Tag]
tags
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
distributionName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf InputOrigin
origin
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf CacheBehavior
defaultCacheBehavior
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
bundleId

instance Data.ToHeaders CreateDistribution where
  toHeaders :: CreateDistribution -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"X-Amz-Target"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"Lightsail_20161128.CreateDistribution" ::
                          Prelude.ByteString
                      ),
            HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON CreateDistribution where
  toJSON :: CreateDistribution -> Value
toJSON CreateDistribution' {Maybe [CacheBehaviorPerPath]
Maybe [Tag]
Maybe IpAddressType
Maybe CacheSettings
Text
CacheBehavior
InputOrigin
bundleId :: Text
defaultCacheBehavior :: CacheBehavior
origin :: InputOrigin
distributionName :: Text
tags :: Maybe [Tag]
ipAddressType :: Maybe IpAddressType
cacheBehaviors :: Maybe [CacheBehaviorPerPath]
cacheBehaviorSettings :: Maybe CacheSettings
$sel:bundleId:CreateDistribution' :: CreateDistribution -> Text
$sel:defaultCacheBehavior:CreateDistribution' :: CreateDistribution -> CacheBehavior
$sel:origin:CreateDistribution' :: CreateDistribution -> InputOrigin
$sel:distributionName:CreateDistribution' :: CreateDistribution -> Text
$sel:tags:CreateDistribution' :: CreateDistribution -> Maybe [Tag]
$sel:ipAddressType:CreateDistribution' :: CreateDistribution -> Maybe IpAddressType
$sel:cacheBehaviors:CreateDistribution' :: CreateDistribution -> Maybe [CacheBehaviorPerPath]
$sel:cacheBehaviorSettings:CreateDistribution' :: CreateDistribution -> Maybe CacheSettings
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"cacheBehaviorSettings" 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 CacheSettings
cacheBehaviorSettings,
            (Key
"cacheBehaviors" 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 [CacheBehaviorPerPath]
cacheBehaviors,
            (Key
"ipAddressType" 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 IpAddressType
ipAddressType,
            (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 [Tag]
tags,
            forall a. a -> Maybe a
Prelude.Just
              (Key
"distributionName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
distributionName),
            forall a. a -> Maybe a
Prelude.Just (Key
"origin" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= InputOrigin
origin),
            forall a. a -> Maybe a
Prelude.Just
              ( Key
"defaultCacheBehavior"
                  forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= CacheBehavior
defaultCacheBehavior
              ),
            forall a. a -> Maybe a
Prelude.Just (Key
"bundleId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
bundleId)
          ]
      )

instance Data.ToPath CreateDistribution where
  toPath :: CreateDistribution -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

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

-- | /See:/ 'newCreateDistributionResponse' smart constructor.
data CreateDistributionResponse = CreateDistributionResponse'
  { -- | An object that describes the distribution created.
    CreateDistributionResponse -> Maybe LightsailDistribution
distribution :: Prelude.Maybe LightsailDistribution,
    -- | An array of objects that describe the result of the action, such as the
    -- status of the request, the timestamp of the request, and the resources
    -- affected by the request.
    CreateDistributionResponse -> Maybe Operation
operation :: Prelude.Maybe Operation,
    -- | The response's http status code.
    CreateDistributionResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (CreateDistributionResponse -> CreateDistributionResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateDistributionResponse -> CreateDistributionResponse -> Bool
$c/= :: CreateDistributionResponse -> CreateDistributionResponse -> Bool
== :: CreateDistributionResponse -> CreateDistributionResponse -> Bool
$c== :: CreateDistributionResponse -> CreateDistributionResponse -> Bool
Prelude.Eq, ReadPrec [CreateDistributionResponse]
ReadPrec CreateDistributionResponse
Int -> ReadS CreateDistributionResponse
ReadS [CreateDistributionResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateDistributionResponse]
$creadListPrec :: ReadPrec [CreateDistributionResponse]
readPrec :: ReadPrec CreateDistributionResponse
$creadPrec :: ReadPrec CreateDistributionResponse
readList :: ReadS [CreateDistributionResponse]
$creadList :: ReadS [CreateDistributionResponse]
readsPrec :: Int -> ReadS CreateDistributionResponse
$creadsPrec :: Int -> ReadS CreateDistributionResponse
Prelude.Read, Int -> CreateDistributionResponse -> ShowS
[CreateDistributionResponse] -> ShowS
CreateDistributionResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateDistributionResponse] -> ShowS
$cshowList :: [CreateDistributionResponse] -> ShowS
show :: CreateDistributionResponse -> String
$cshow :: CreateDistributionResponse -> String
showsPrec :: Int -> CreateDistributionResponse -> ShowS
$cshowsPrec :: Int -> CreateDistributionResponse -> ShowS
Prelude.Show, forall x.
Rep CreateDistributionResponse x -> CreateDistributionResponse
forall x.
CreateDistributionResponse -> Rep CreateDistributionResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CreateDistributionResponse x -> CreateDistributionResponse
$cfrom :: forall x.
CreateDistributionResponse -> Rep CreateDistributionResponse x
Prelude.Generic)

-- |
-- Create a value of 'CreateDistributionResponse' 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:
--
-- 'distribution', 'createDistributionResponse_distribution' - An object that describes the distribution created.
--
-- 'operation', 'createDistributionResponse_operation' - An array of objects that describe the result of the action, such as the
-- status of the request, the timestamp of the request, and the resources
-- affected by the request.
--
-- 'httpStatus', 'createDistributionResponse_httpStatus' - The response's http status code.
newCreateDistributionResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  CreateDistributionResponse
newCreateDistributionResponse :: Int -> CreateDistributionResponse
newCreateDistributionResponse Int
pHttpStatus_ =
  CreateDistributionResponse'
    { $sel:distribution:CreateDistributionResponse' :: Maybe LightsailDistribution
distribution =
        forall a. Maybe a
Prelude.Nothing,
      $sel:operation:CreateDistributionResponse' :: Maybe Operation
operation = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:CreateDistributionResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | An object that describes the distribution created.
createDistributionResponse_distribution :: Lens.Lens' CreateDistributionResponse (Prelude.Maybe LightsailDistribution)
createDistributionResponse_distribution :: Lens' CreateDistributionResponse (Maybe LightsailDistribution)
createDistributionResponse_distribution = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateDistributionResponse' {Maybe LightsailDistribution
distribution :: Maybe LightsailDistribution
$sel:distribution:CreateDistributionResponse' :: CreateDistributionResponse -> Maybe LightsailDistribution
distribution} -> Maybe LightsailDistribution
distribution) (\s :: CreateDistributionResponse
s@CreateDistributionResponse' {} Maybe LightsailDistribution
a -> CreateDistributionResponse
s {$sel:distribution:CreateDistributionResponse' :: Maybe LightsailDistribution
distribution = Maybe LightsailDistribution
a} :: CreateDistributionResponse)

-- | An array of objects that describe the result of the action, such as the
-- status of the request, the timestamp of the request, and the resources
-- affected by the request.
createDistributionResponse_operation :: Lens.Lens' CreateDistributionResponse (Prelude.Maybe Operation)
createDistributionResponse_operation :: Lens' CreateDistributionResponse (Maybe Operation)
createDistributionResponse_operation = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateDistributionResponse' {Maybe Operation
operation :: Maybe Operation
$sel:operation:CreateDistributionResponse' :: CreateDistributionResponse -> Maybe Operation
operation} -> Maybe Operation
operation) (\s :: CreateDistributionResponse
s@CreateDistributionResponse' {} Maybe Operation
a -> CreateDistributionResponse
s {$sel:operation:CreateDistributionResponse' :: Maybe Operation
operation = Maybe Operation
a} :: CreateDistributionResponse)

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

instance Prelude.NFData CreateDistributionResponse where
  rnf :: CreateDistributionResponse -> ()
rnf CreateDistributionResponse' {Int
Maybe Operation
Maybe LightsailDistribution
httpStatus :: Int
operation :: Maybe Operation
distribution :: Maybe LightsailDistribution
$sel:httpStatus:CreateDistributionResponse' :: CreateDistributionResponse -> Int
$sel:operation:CreateDistributionResponse' :: CreateDistributionResponse -> Maybe Operation
$sel:distribution:CreateDistributionResponse' :: CreateDistributionResponse -> Maybe LightsailDistribution
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe LightsailDistribution
distribution
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Operation
operation
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus