{-# 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.Config.DeliverConfigSnapshot
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Schedules delivery of a configuration snapshot to the Amazon S3 bucket
-- in the specified delivery channel. After the delivery has started,
-- Config sends the following notifications using an Amazon SNS topic that
-- you have specified.
--
-- -   Notification of the start of the delivery.
--
-- -   Notification of the completion of the delivery, if the delivery was
--     successfully completed.
--
-- -   Notification of delivery failure, if the delivery failed.
module Amazonka.Config.DeliverConfigSnapshot
  ( -- * Creating a Request
    DeliverConfigSnapshot (..),
    newDeliverConfigSnapshot,

    -- * Request Lenses
    deliverConfigSnapshot_deliveryChannelName,

    -- * Destructuring the Response
    DeliverConfigSnapshotResponse (..),
    newDeliverConfigSnapshotResponse,

    -- * Response Lenses
    deliverConfigSnapshotResponse_configSnapshotId,
    deliverConfigSnapshotResponse_httpStatus,
  )
where

import Amazonka.Config.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 input for the DeliverConfigSnapshot action.
--
-- /See:/ 'newDeliverConfigSnapshot' smart constructor.
data DeliverConfigSnapshot = DeliverConfigSnapshot'
  { -- | The name of the delivery channel through which the snapshot is
    -- delivered.
    DeliverConfigSnapshot -> Text
deliveryChannelName :: Prelude.Text
  }
  deriving (DeliverConfigSnapshot -> DeliverConfigSnapshot -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeliverConfigSnapshot -> DeliverConfigSnapshot -> Bool
$c/= :: DeliverConfigSnapshot -> DeliverConfigSnapshot -> Bool
== :: DeliverConfigSnapshot -> DeliverConfigSnapshot -> Bool
$c== :: DeliverConfigSnapshot -> DeliverConfigSnapshot -> Bool
Prelude.Eq, ReadPrec [DeliverConfigSnapshot]
ReadPrec DeliverConfigSnapshot
Int -> ReadS DeliverConfigSnapshot
ReadS [DeliverConfigSnapshot]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeliverConfigSnapshot]
$creadListPrec :: ReadPrec [DeliverConfigSnapshot]
readPrec :: ReadPrec DeliverConfigSnapshot
$creadPrec :: ReadPrec DeliverConfigSnapshot
readList :: ReadS [DeliverConfigSnapshot]
$creadList :: ReadS [DeliverConfigSnapshot]
readsPrec :: Int -> ReadS DeliverConfigSnapshot
$creadsPrec :: Int -> ReadS DeliverConfigSnapshot
Prelude.Read, Int -> DeliverConfigSnapshot -> ShowS
[DeliverConfigSnapshot] -> ShowS
DeliverConfigSnapshot -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeliverConfigSnapshot] -> ShowS
$cshowList :: [DeliverConfigSnapshot] -> ShowS
show :: DeliverConfigSnapshot -> String
$cshow :: DeliverConfigSnapshot -> String
showsPrec :: Int -> DeliverConfigSnapshot -> ShowS
$cshowsPrec :: Int -> DeliverConfigSnapshot -> ShowS
Prelude.Show, forall x. Rep DeliverConfigSnapshot x -> DeliverConfigSnapshot
forall x. DeliverConfigSnapshot -> Rep DeliverConfigSnapshot x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeliverConfigSnapshot x -> DeliverConfigSnapshot
$cfrom :: forall x. DeliverConfigSnapshot -> Rep DeliverConfigSnapshot x
Prelude.Generic)

-- |
-- Create a value of 'DeliverConfigSnapshot' 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:
--
-- 'deliveryChannelName', 'deliverConfigSnapshot_deliveryChannelName' - The name of the delivery channel through which the snapshot is
-- delivered.
newDeliverConfigSnapshot ::
  -- | 'deliveryChannelName'
  Prelude.Text ->
  DeliverConfigSnapshot
newDeliverConfigSnapshot :: Text -> DeliverConfigSnapshot
newDeliverConfigSnapshot Text
pDeliveryChannelName_ =
  DeliverConfigSnapshot'
    { $sel:deliveryChannelName:DeliverConfigSnapshot' :: Text
deliveryChannelName =
        Text
pDeliveryChannelName_
    }

-- | The name of the delivery channel through which the snapshot is
-- delivered.
deliverConfigSnapshot_deliveryChannelName :: Lens.Lens' DeliverConfigSnapshot Prelude.Text
deliverConfigSnapshot_deliveryChannelName :: Lens' DeliverConfigSnapshot Text
deliverConfigSnapshot_deliveryChannelName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeliverConfigSnapshot' {Text
deliveryChannelName :: Text
$sel:deliveryChannelName:DeliverConfigSnapshot' :: DeliverConfigSnapshot -> Text
deliveryChannelName} -> Text
deliveryChannelName) (\s :: DeliverConfigSnapshot
s@DeliverConfigSnapshot' {} Text
a -> DeliverConfigSnapshot
s {$sel:deliveryChannelName:DeliverConfigSnapshot' :: Text
deliveryChannelName = Text
a} :: DeliverConfigSnapshot)

instance Core.AWSRequest DeliverConfigSnapshot where
  type
    AWSResponse DeliverConfigSnapshot =
      DeliverConfigSnapshotResponse
  request :: (Service -> Service)
-> DeliverConfigSnapshot -> Request DeliverConfigSnapshot
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 DeliverConfigSnapshot
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DeliverConfigSnapshot)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> Object -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveJSON
      ( \Int
s ResponseHeaders
h Object
x ->
          Maybe Text -> Int -> DeliverConfigSnapshotResponse
DeliverConfigSnapshotResponse'
            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
"configSnapshotId")
            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 DeliverConfigSnapshot where
  hashWithSalt :: Int -> DeliverConfigSnapshot -> Int
hashWithSalt Int
_salt DeliverConfigSnapshot' {Text
deliveryChannelName :: Text
$sel:deliveryChannelName:DeliverConfigSnapshot' :: DeliverConfigSnapshot -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
deliveryChannelName

instance Prelude.NFData DeliverConfigSnapshot where
  rnf :: DeliverConfigSnapshot -> ()
rnf DeliverConfigSnapshot' {Text
deliveryChannelName :: Text
$sel:deliveryChannelName:DeliverConfigSnapshot' :: DeliverConfigSnapshot -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
deliveryChannelName

instance Data.ToHeaders DeliverConfigSnapshot where
  toHeaders :: DeliverConfigSnapshot -> 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
"StarlingDoveService.DeliverConfigSnapshot" ::
                          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 DeliverConfigSnapshot where
  toJSON :: DeliverConfigSnapshot -> Value
toJSON DeliverConfigSnapshot' {Text
deliveryChannelName :: Text
$sel:deliveryChannelName:DeliverConfigSnapshot' :: DeliverConfigSnapshot -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ forall a. a -> Maybe a
Prelude.Just
              (Key
"deliveryChannelName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
deliveryChannelName)
          ]
      )

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

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

-- | The output for the DeliverConfigSnapshot action, in JSON format.
--
-- /See:/ 'newDeliverConfigSnapshotResponse' smart constructor.
data DeliverConfigSnapshotResponse = DeliverConfigSnapshotResponse'
  { -- | The ID of the snapshot that is being created.
    DeliverConfigSnapshotResponse -> Maybe Text
configSnapshotId :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    DeliverConfigSnapshotResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DeliverConfigSnapshotResponse
-> DeliverConfigSnapshotResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeliverConfigSnapshotResponse
-> DeliverConfigSnapshotResponse -> Bool
$c/= :: DeliverConfigSnapshotResponse
-> DeliverConfigSnapshotResponse -> Bool
== :: DeliverConfigSnapshotResponse
-> DeliverConfigSnapshotResponse -> Bool
$c== :: DeliverConfigSnapshotResponse
-> DeliverConfigSnapshotResponse -> Bool
Prelude.Eq, ReadPrec [DeliverConfigSnapshotResponse]
ReadPrec DeliverConfigSnapshotResponse
Int -> ReadS DeliverConfigSnapshotResponse
ReadS [DeliverConfigSnapshotResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeliverConfigSnapshotResponse]
$creadListPrec :: ReadPrec [DeliverConfigSnapshotResponse]
readPrec :: ReadPrec DeliverConfigSnapshotResponse
$creadPrec :: ReadPrec DeliverConfigSnapshotResponse
readList :: ReadS [DeliverConfigSnapshotResponse]
$creadList :: ReadS [DeliverConfigSnapshotResponse]
readsPrec :: Int -> ReadS DeliverConfigSnapshotResponse
$creadsPrec :: Int -> ReadS DeliverConfigSnapshotResponse
Prelude.Read, Int -> DeliverConfigSnapshotResponse -> ShowS
[DeliverConfigSnapshotResponse] -> ShowS
DeliverConfigSnapshotResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeliverConfigSnapshotResponse] -> ShowS
$cshowList :: [DeliverConfigSnapshotResponse] -> ShowS
show :: DeliverConfigSnapshotResponse -> String
$cshow :: DeliverConfigSnapshotResponse -> String
showsPrec :: Int -> DeliverConfigSnapshotResponse -> ShowS
$cshowsPrec :: Int -> DeliverConfigSnapshotResponse -> ShowS
Prelude.Show, forall x.
Rep DeliverConfigSnapshotResponse x
-> DeliverConfigSnapshotResponse
forall x.
DeliverConfigSnapshotResponse
-> Rep DeliverConfigSnapshotResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DeliverConfigSnapshotResponse x
-> DeliverConfigSnapshotResponse
$cfrom :: forall x.
DeliverConfigSnapshotResponse
-> Rep DeliverConfigSnapshotResponse x
Prelude.Generic)

-- |
-- Create a value of 'DeliverConfigSnapshotResponse' 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:
--
-- 'configSnapshotId', 'deliverConfigSnapshotResponse_configSnapshotId' - The ID of the snapshot that is being created.
--
-- 'httpStatus', 'deliverConfigSnapshotResponse_httpStatus' - The response's http status code.
newDeliverConfigSnapshotResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DeliverConfigSnapshotResponse
newDeliverConfigSnapshotResponse :: Int -> DeliverConfigSnapshotResponse
newDeliverConfigSnapshotResponse Int
pHttpStatus_ =
  DeliverConfigSnapshotResponse'
    { $sel:configSnapshotId:DeliverConfigSnapshotResponse' :: Maybe Text
configSnapshotId =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DeliverConfigSnapshotResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The ID of the snapshot that is being created.
deliverConfigSnapshotResponse_configSnapshotId :: Lens.Lens' DeliverConfigSnapshotResponse (Prelude.Maybe Prelude.Text)
deliverConfigSnapshotResponse_configSnapshotId :: Lens' DeliverConfigSnapshotResponse (Maybe Text)
deliverConfigSnapshotResponse_configSnapshotId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeliverConfigSnapshotResponse' {Maybe Text
configSnapshotId :: Maybe Text
$sel:configSnapshotId:DeliverConfigSnapshotResponse' :: DeliverConfigSnapshotResponse -> Maybe Text
configSnapshotId} -> Maybe Text
configSnapshotId) (\s :: DeliverConfigSnapshotResponse
s@DeliverConfigSnapshotResponse' {} Maybe Text
a -> DeliverConfigSnapshotResponse
s {$sel:configSnapshotId:DeliverConfigSnapshotResponse' :: Maybe Text
configSnapshotId = Maybe Text
a} :: DeliverConfigSnapshotResponse)

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

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