{-# 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.CloudFront.CreateInvalidation
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Create a new invalidation.
module Amazonka.CloudFront.CreateInvalidation
  ( -- * Creating a Request
    CreateInvalidation (..),
    newCreateInvalidation,

    -- * Request Lenses
    createInvalidation_distributionId,
    createInvalidation_invalidationBatch,

    -- * Destructuring the Response
    CreateInvalidationResponse (..),
    newCreateInvalidationResponse,

    -- * Response Lenses
    createInvalidationResponse_invalidation,
    createInvalidationResponse_location,
    createInvalidationResponse_httpStatus,
  )
where

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

-- | The request to create an invalidation.
--
-- /See:/ 'newCreateInvalidation' smart constructor.
data CreateInvalidation = CreateInvalidation'
  { -- | The distribution\'s id.
    CreateInvalidation -> Text
distributionId :: Prelude.Text,
    -- | The batch information for the invalidation.
    CreateInvalidation -> InvalidationBatch
invalidationBatch :: InvalidationBatch
  }
  deriving (CreateInvalidation -> CreateInvalidation -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateInvalidation -> CreateInvalidation -> Bool
$c/= :: CreateInvalidation -> CreateInvalidation -> Bool
== :: CreateInvalidation -> CreateInvalidation -> Bool
$c== :: CreateInvalidation -> CreateInvalidation -> Bool
Prelude.Eq, ReadPrec [CreateInvalidation]
ReadPrec CreateInvalidation
Int -> ReadS CreateInvalidation
ReadS [CreateInvalidation]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateInvalidation]
$creadListPrec :: ReadPrec [CreateInvalidation]
readPrec :: ReadPrec CreateInvalidation
$creadPrec :: ReadPrec CreateInvalidation
readList :: ReadS [CreateInvalidation]
$creadList :: ReadS [CreateInvalidation]
readsPrec :: Int -> ReadS CreateInvalidation
$creadsPrec :: Int -> ReadS CreateInvalidation
Prelude.Read, Int -> CreateInvalidation -> ShowS
[CreateInvalidation] -> ShowS
CreateInvalidation -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateInvalidation] -> ShowS
$cshowList :: [CreateInvalidation] -> ShowS
show :: CreateInvalidation -> String
$cshow :: CreateInvalidation -> String
showsPrec :: Int -> CreateInvalidation -> ShowS
$cshowsPrec :: Int -> CreateInvalidation -> ShowS
Prelude.Show, forall x. Rep CreateInvalidation x -> CreateInvalidation
forall x. CreateInvalidation -> Rep CreateInvalidation x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateInvalidation x -> CreateInvalidation
$cfrom :: forall x. CreateInvalidation -> Rep CreateInvalidation x
Prelude.Generic)

-- |
-- Create a value of 'CreateInvalidation' 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:
--
-- 'distributionId', 'createInvalidation_distributionId' - The distribution\'s id.
--
-- 'invalidationBatch', 'createInvalidation_invalidationBatch' - The batch information for the invalidation.
newCreateInvalidation ::
  -- | 'distributionId'
  Prelude.Text ->
  -- | 'invalidationBatch'
  InvalidationBatch ->
  CreateInvalidation
newCreateInvalidation :: Text -> InvalidationBatch -> CreateInvalidation
newCreateInvalidation
  Text
pDistributionId_
  InvalidationBatch
pInvalidationBatch_ =
    CreateInvalidation'
      { $sel:distributionId:CreateInvalidation' :: Text
distributionId =
          Text
pDistributionId_,
        $sel:invalidationBatch:CreateInvalidation' :: InvalidationBatch
invalidationBatch = InvalidationBatch
pInvalidationBatch_
      }

-- | The distribution\'s id.
createInvalidation_distributionId :: Lens.Lens' CreateInvalidation Prelude.Text
createInvalidation_distributionId :: Lens' CreateInvalidation Text
createInvalidation_distributionId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateInvalidation' {Text
distributionId :: Text
$sel:distributionId:CreateInvalidation' :: CreateInvalidation -> Text
distributionId} -> Text
distributionId) (\s :: CreateInvalidation
s@CreateInvalidation' {} Text
a -> CreateInvalidation
s {$sel:distributionId:CreateInvalidation' :: Text
distributionId = Text
a} :: CreateInvalidation)

-- | The batch information for the invalidation.
createInvalidation_invalidationBatch :: Lens.Lens' CreateInvalidation InvalidationBatch
createInvalidation_invalidationBatch :: Lens' CreateInvalidation InvalidationBatch
createInvalidation_invalidationBatch = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateInvalidation' {InvalidationBatch
invalidationBatch :: InvalidationBatch
$sel:invalidationBatch:CreateInvalidation' :: CreateInvalidation -> InvalidationBatch
invalidationBatch} -> InvalidationBatch
invalidationBatch) (\s :: CreateInvalidation
s@CreateInvalidation' {} InvalidationBatch
a -> CreateInvalidation
s {$sel:invalidationBatch:CreateInvalidation' :: InvalidationBatch
invalidationBatch = InvalidationBatch
a} :: CreateInvalidation)

instance Core.AWSRequest CreateInvalidation where
  type
    AWSResponse CreateInvalidation =
      CreateInvalidationResponse
  request :: (Service -> Service)
-> CreateInvalidation -> Request CreateInvalidation
request Service -> Service
overrides =
    forall a. (ToRequest a, ToElement a) => Service -> a -> Request a
Request.postXML (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy CreateInvalidation
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse CreateInvalidation)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> [Node] -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveXML
      ( \Int
s ResponseHeaders
h [Node]
x ->
          Maybe Invalidation
-> Maybe Text -> Int -> CreateInvalidationResponse
CreateInvalidationResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (forall a. FromXML a => [Node] -> Either String a
Data.parseXML [Node]
x)
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (ResponseHeaders
h forall a.
FromText a =>
ResponseHeaders -> HeaderName -> Either String (Maybe a)
Data..#? HeaderName
"Location")
            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 CreateInvalidation where
  hashWithSalt :: Int -> CreateInvalidation -> Int
hashWithSalt Int
_salt CreateInvalidation' {Text
InvalidationBatch
invalidationBatch :: InvalidationBatch
distributionId :: Text
$sel:invalidationBatch:CreateInvalidation' :: CreateInvalidation -> InvalidationBatch
$sel:distributionId:CreateInvalidation' :: CreateInvalidation -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
distributionId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` InvalidationBatch
invalidationBatch

instance Prelude.NFData CreateInvalidation where
  rnf :: CreateInvalidation -> ()
rnf CreateInvalidation' {Text
InvalidationBatch
invalidationBatch :: InvalidationBatch
distributionId :: Text
$sel:invalidationBatch:CreateInvalidation' :: CreateInvalidation -> InvalidationBatch
$sel:distributionId:CreateInvalidation' :: CreateInvalidation -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
distributionId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf InvalidationBatch
invalidationBatch

instance Data.ToElement CreateInvalidation where
  toElement :: CreateInvalidation -> Element
toElement CreateInvalidation' {Text
InvalidationBatch
invalidationBatch :: InvalidationBatch
distributionId :: Text
$sel:invalidationBatch:CreateInvalidation' :: CreateInvalidation -> InvalidationBatch
$sel:distributionId:CreateInvalidation' :: CreateInvalidation -> Text
..} =
    forall a. ToXML a => Name -> a -> Element
Data.mkElement
      Name
"{http://cloudfront.amazonaws.com/doc/2020-05-31/}InvalidationBatch"
      InvalidationBatch
invalidationBatch

instance Data.ToHeaders CreateInvalidation where
  toHeaders :: CreateInvalidation -> ResponseHeaders
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

instance Data.ToPath CreateInvalidation where
  toPath :: CreateInvalidation -> ByteString
toPath CreateInvalidation' {Text
InvalidationBatch
invalidationBatch :: InvalidationBatch
distributionId :: Text
$sel:invalidationBatch:CreateInvalidation' :: CreateInvalidation -> InvalidationBatch
$sel:distributionId:CreateInvalidation' :: CreateInvalidation -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/2020-05-31/distribution/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
distributionId,
        ByteString
"/invalidation"
      ]

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

-- | The returned result of the corresponding request.
--
-- /See:/ 'newCreateInvalidationResponse' smart constructor.
data CreateInvalidationResponse = CreateInvalidationResponse'
  { -- | The invalidation\'s information.
    CreateInvalidationResponse -> Maybe Invalidation
invalidation :: Prelude.Maybe Invalidation,
    -- | The fully qualified URI of the distribution and invalidation batch
    -- request, including the @Invalidation ID@.
    CreateInvalidationResponse -> Maybe Text
location :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    CreateInvalidationResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (CreateInvalidationResponse -> CreateInvalidationResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateInvalidationResponse -> CreateInvalidationResponse -> Bool
$c/= :: CreateInvalidationResponse -> CreateInvalidationResponse -> Bool
== :: CreateInvalidationResponse -> CreateInvalidationResponse -> Bool
$c== :: CreateInvalidationResponse -> CreateInvalidationResponse -> Bool
Prelude.Eq, ReadPrec [CreateInvalidationResponse]
ReadPrec CreateInvalidationResponse
Int -> ReadS CreateInvalidationResponse
ReadS [CreateInvalidationResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateInvalidationResponse]
$creadListPrec :: ReadPrec [CreateInvalidationResponse]
readPrec :: ReadPrec CreateInvalidationResponse
$creadPrec :: ReadPrec CreateInvalidationResponse
readList :: ReadS [CreateInvalidationResponse]
$creadList :: ReadS [CreateInvalidationResponse]
readsPrec :: Int -> ReadS CreateInvalidationResponse
$creadsPrec :: Int -> ReadS CreateInvalidationResponse
Prelude.Read, Int -> CreateInvalidationResponse -> ShowS
[CreateInvalidationResponse] -> ShowS
CreateInvalidationResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateInvalidationResponse] -> ShowS
$cshowList :: [CreateInvalidationResponse] -> ShowS
show :: CreateInvalidationResponse -> String
$cshow :: CreateInvalidationResponse -> String
showsPrec :: Int -> CreateInvalidationResponse -> ShowS
$cshowsPrec :: Int -> CreateInvalidationResponse -> ShowS
Prelude.Show, forall x.
Rep CreateInvalidationResponse x -> CreateInvalidationResponse
forall x.
CreateInvalidationResponse -> Rep CreateInvalidationResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CreateInvalidationResponse x -> CreateInvalidationResponse
$cfrom :: forall x.
CreateInvalidationResponse -> Rep CreateInvalidationResponse x
Prelude.Generic)

-- |
-- Create a value of 'CreateInvalidationResponse' 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:
--
-- 'invalidation', 'createInvalidationResponse_invalidation' - The invalidation\'s information.
--
-- 'location', 'createInvalidationResponse_location' - The fully qualified URI of the distribution and invalidation batch
-- request, including the @Invalidation ID@.
--
-- 'httpStatus', 'createInvalidationResponse_httpStatus' - The response's http status code.
newCreateInvalidationResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  CreateInvalidationResponse
newCreateInvalidationResponse :: Int -> CreateInvalidationResponse
newCreateInvalidationResponse Int
pHttpStatus_ =
  CreateInvalidationResponse'
    { $sel:invalidation:CreateInvalidationResponse' :: Maybe Invalidation
invalidation =
        forall a. Maybe a
Prelude.Nothing,
      $sel:location:CreateInvalidationResponse' :: Maybe Text
location = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:CreateInvalidationResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The invalidation\'s information.
createInvalidationResponse_invalidation :: Lens.Lens' CreateInvalidationResponse (Prelude.Maybe Invalidation)
createInvalidationResponse_invalidation :: Lens' CreateInvalidationResponse (Maybe Invalidation)
createInvalidationResponse_invalidation = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateInvalidationResponse' {Maybe Invalidation
invalidation :: Maybe Invalidation
$sel:invalidation:CreateInvalidationResponse' :: CreateInvalidationResponse -> Maybe Invalidation
invalidation} -> Maybe Invalidation
invalidation) (\s :: CreateInvalidationResponse
s@CreateInvalidationResponse' {} Maybe Invalidation
a -> CreateInvalidationResponse
s {$sel:invalidation:CreateInvalidationResponse' :: Maybe Invalidation
invalidation = Maybe Invalidation
a} :: CreateInvalidationResponse)

-- | The fully qualified URI of the distribution and invalidation batch
-- request, including the @Invalidation ID@.
createInvalidationResponse_location :: Lens.Lens' CreateInvalidationResponse (Prelude.Maybe Prelude.Text)
createInvalidationResponse_location :: Lens' CreateInvalidationResponse (Maybe Text)
createInvalidationResponse_location = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateInvalidationResponse' {Maybe Text
location :: Maybe Text
$sel:location:CreateInvalidationResponse' :: CreateInvalidationResponse -> Maybe Text
location} -> Maybe Text
location) (\s :: CreateInvalidationResponse
s@CreateInvalidationResponse' {} Maybe Text
a -> CreateInvalidationResponse
s {$sel:location:CreateInvalidationResponse' :: Maybe Text
location = Maybe Text
a} :: CreateInvalidationResponse)

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

instance Prelude.NFData CreateInvalidationResponse where
  rnf :: CreateInvalidationResponse -> ()
rnf CreateInvalidationResponse' {Int
Maybe Text
Maybe Invalidation
httpStatus :: Int
location :: Maybe Text
invalidation :: Maybe Invalidation
$sel:httpStatus:CreateInvalidationResponse' :: CreateInvalidationResponse -> Int
$sel:location:CreateInvalidationResponse' :: CreateInvalidationResponse -> Maybe Text
$sel:invalidation:CreateInvalidationResponse' :: CreateInvalidationResponse -> Maybe Invalidation
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Invalidation
invalidation
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
location
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus