{-# 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.RedshiftServerLess.CreateSnapshot
-- 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 snapshot of all databases in a namespace. For more information
-- about snapshots, see
-- <https://docs.aws.amazon.com/redshift/latest/mgmt/serverless-snapshots-recovery.html Working with snapshots and recovery points>.
module Amazonka.RedshiftServerLess.CreateSnapshot
  ( -- * Creating a Request
    CreateSnapshot (..),
    newCreateSnapshot,

    -- * Request Lenses
    createSnapshot_retentionPeriod,
    createSnapshot_tags,
    createSnapshot_namespaceName,
    createSnapshot_snapshotName,

    -- * Destructuring the Response
    CreateSnapshotResponse (..),
    newCreateSnapshotResponse,

    -- * Response Lenses
    createSnapshotResponse_snapshot,
    createSnapshotResponse_httpStatus,
  )
where

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 Amazonka.RedshiftServerLess.Types
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newCreateSnapshot' smart constructor.
data CreateSnapshot = CreateSnapshot'
  { -- | How long to retain the created snapshot.
    CreateSnapshot -> Maybe Int
retentionPeriod :: Prelude.Maybe Prelude.Int,
    -- | An array of
    -- <https://docs.aws.amazon.com/redshift-serverless/latest/APIReference/API_Tag.html Tag objects>
    -- to associate with the snapshot.
    CreateSnapshot -> Maybe [Tag]
tags :: Prelude.Maybe [Tag],
    -- | The namespace to create a snapshot for.
    CreateSnapshot -> Text
namespaceName :: Prelude.Text,
    -- | The name of the snapshot.
    CreateSnapshot -> Text
snapshotName :: Prelude.Text
  }
  deriving (CreateSnapshot -> CreateSnapshot -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateSnapshot -> CreateSnapshot -> Bool
$c/= :: CreateSnapshot -> CreateSnapshot -> Bool
== :: CreateSnapshot -> CreateSnapshot -> Bool
$c== :: CreateSnapshot -> CreateSnapshot -> Bool
Prelude.Eq, ReadPrec [CreateSnapshot]
ReadPrec CreateSnapshot
Int -> ReadS CreateSnapshot
ReadS [CreateSnapshot]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateSnapshot]
$creadListPrec :: ReadPrec [CreateSnapshot]
readPrec :: ReadPrec CreateSnapshot
$creadPrec :: ReadPrec CreateSnapshot
readList :: ReadS [CreateSnapshot]
$creadList :: ReadS [CreateSnapshot]
readsPrec :: Int -> ReadS CreateSnapshot
$creadsPrec :: Int -> ReadS CreateSnapshot
Prelude.Read, Int -> CreateSnapshot -> ShowS
[CreateSnapshot] -> ShowS
CreateSnapshot -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateSnapshot] -> ShowS
$cshowList :: [CreateSnapshot] -> ShowS
show :: CreateSnapshot -> String
$cshow :: CreateSnapshot -> String
showsPrec :: Int -> CreateSnapshot -> ShowS
$cshowsPrec :: Int -> CreateSnapshot -> ShowS
Prelude.Show, forall x. Rep CreateSnapshot x -> CreateSnapshot
forall x. CreateSnapshot -> Rep CreateSnapshot x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateSnapshot x -> CreateSnapshot
$cfrom :: forall x. CreateSnapshot -> Rep CreateSnapshot x
Prelude.Generic)

-- |
-- Create a value of 'CreateSnapshot' 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:
--
-- 'retentionPeriod', 'createSnapshot_retentionPeriod' - How long to retain the created snapshot.
--
-- 'tags', 'createSnapshot_tags' - An array of
-- <https://docs.aws.amazon.com/redshift-serverless/latest/APIReference/API_Tag.html Tag objects>
-- to associate with the snapshot.
--
-- 'namespaceName', 'createSnapshot_namespaceName' - The namespace to create a snapshot for.
--
-- 'snapshotName', 'createSnapshot_snapshotName' - The name of the snapshot.
newCreateSnapshot ::
  -- | 'namespaceName'
  Prelude.Text ->
  -- | 'snapshotName'
  Prelude.Text ->
  CreateSnapshot
newCreateSnapshot :: Text -> Text -> CreateSnapshot
newCreateSnapshot Text
pNamespaceName_ Text
pSnapshotName_ =
  CreateSnapshot'
    { $sel:retentionPeriod:CreateSnapshot' :: Maybe Int
retentionPeriod = forall a. Maybe a
Prelude.Nothing,
      $sel:tags:CreateSnapshot' :: Maybe [Tag]
tags = forall a. Maybe a
Prelude.Nothing,
      $sel:namespaceName:CreateSnapshot' :: Text
namespaceName = Text
pNamespaceName_,
      $sel:snapshotName:CreateSnapshot' :: Text
snapshotName = Text
pSnapshotName_
    }

-- | How long to retain the created snapshot.
createSnapshot_retentionPeriod :: Lens.Lens' CreateSnapshot (Prelude.Maybe Prelude.Int)
createSnapshot_retentionPeriod :: Lens' CreateSnapshot (Maybe Int)
createSnapshot_retentionPeriod = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateSnapshot' {Maybe Int
retentionPeriod :: Maybe Int
$sel:retentionPeriod:CreateSnapshot' :: CreateSnapshot -> Maybe Int
retentionPeriod} -> Maybe Int
retentionPeriod) (\s :: CreateSnapshot
s@CreateSnapshot' {} Maybe Int
a -> CreateSnapshot
s {$sel:retentionPeriod:CreateSnapshot' :: Maybe Int
retentionPeriod = Maybe Int
a} :: CreateSnapshot)

-- | An array of
-- <https://docs.aws.amazon.com/redshift-serverless/latest/APIReference/API_Tag.html Tag objects>
-- to associate with the snapshot.
createSnapshot_tags :: Lens.Lens' CreateSnapshot (Prelude.Maybe [Tag])
createSnapshot_tags :: Lens' CreateSnapshot (Maybe [Tag])
createSnapshot_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateSnapshot' {Maybe [Tag]
tags :: Maybe [Tag]
$sel:tags:CreateSnapshot' :: CreateSnapshot -> Maybe [Tag]
tags} -> Maybe [Tag]
tags) (\s :: CreateSnapshot
s@CreateSnapshot' {} Maybe [Tag]
a -> CreateSnapshot
s {$sel:tags:CreateSnapshot' :: Maybe [Tag]
tags = Maybe [Tag]
a} :: CreateSnapshot) 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 namespace to create a snapshot for.
createSnapshot_namespaceName :: Lens.Lens' CreateSnapshot Prelude.Text
createSnapshot_namespaceName :: Lens' CreateSnapshot Text
createSnapshot_namespaceName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateSnapshot' {Text
namespaceName :: Text
$sel:namespaceName:CreateSnapshot' :: CreateSnapshot -> Text
namespaceName} -> Text
namespaceName) (\s :: CreateSnapshot
s@CreateSnapshot' {} Text
a -> CreateSnapshot
s {$sel:namespaceName:CreateSnapshot' :: Text
namespaceName = Text
a} :: CreateSnapshot)

-- | The name of the snapshot.
createSnapshot_snapshotName :: Lens.Lens' CreateSnapshot Prelude.Text
createSnapshot_snapshotName :: Lens' CreateSnapshot Text
createSnapshot_snapshotName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateSnapshot' {Text
snapshotName :: Text
$sel:snapshotName:CreateSnapshot' :: CreateSnapshot -> Text
snapshotName} -> Text
snapshotName) (\s :: CreateSnapshot
s@CreateSnapshot' {} Text
a -> CreateSnapshot
s {$sel:snapshotName:CreateSnapshot' :: Text
snapshotName = Text
a} :: CreateSnapshot)

instance Core.AWSRequest CreateSnapshot where
  type
    AWSResponse CreateSnapshot =
      CreateSnapshotResponse
  request :: (Service -> Service) -> CreateSnapshot -> Request CreateSnapshot
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 CreateSnapshot
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse CreateSnapshot)))
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 Snapshot -> Int -> CreateSnapshotResponse
CreateSnapshotResponse'
            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
"snapshot")
            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 CreateSnapshot where
  hashWithSalt :: Int -> CreateSnapshot -> Int
hashWithSalt Int
_salt CreateSnapshot' {Maybe Int
Maybe [Tag]
Text
snapshotName :: Text
namespaceName :: Text
tags :: Maybe [Tag]
retentionPeriod :: Maybe Int
$sel:snapshotName:CreateSnapshot' :: CreateSnapshot -> Text
$sel:namespaceName:CreateSnapshot' :: CreateSnapshot -> Text
$sel:tags:CreateSnapshot' :: CreateSnapshot -> Maybe [Tag]
$sel:retentionPeriod:CreateSnapshot' :: CreateSnapshot -> Maybe Int
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
retentionPeriod
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Tag]
tags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
namespaceName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
snapshotName

instance Prelude.NFData CreateSnapshot where
  rnf :: CreateSnapshot -> ()
rnf CreateSnapshot' {Maybe Int
Maybe [Tag]
Text
snapshotName :: Text
namespaceName :: Text
tags :: Maybe [Tag]
retentionPeriod :: Maybe Int
$sel:snapshotName:CreateSnapshot' :: CreateSnapshot -> Text
$sel:namespaceName:CreateSnapshot' :: CreateSnapshot -> Text
$sel:tags:CreateSnapshot' :: CreateSnapshot -> Maybe [Tag]
$sel:retentionPeriod:CreateSnapshot' :: CreateSnapshot -> Maybe Int
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
retentionPeriod
      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
namespaceName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
snapshotName

instance Data.ToHeaders CreateSnapshot where
  toHeaders :: CreateSnapshot -> 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
"RedshiftServerless.CreateSnapshot" ::
                          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 CreateSnapshot where
  toJSON :: CreateSnapshot -> Value
toJSON CreateSnapshot' {Maybe Int
Maybe [Tag]
Text
snapshotName :: Text
namespaceName :: Text
tags :: Maybe [Tag]
retentionPeriod :: Maybe Int
$sel:snapshotName:CreateSnapshot' :: CreateSnapshot -> Text
$sel:namespaceName:CreateSnapshot' :: CreateSnapshot -> Text
$sel:tags:CreateSnapshot' :: CreateSnapshot -> Maybe [Tag]
$sel:retentionPeriod:CreateSnapshot' :: CreateSnapshot -> Maybe Int
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"retentionPeriod" 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 Int
retentionPeriod,
            (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
"namespaceName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
namespaceName),
            forall a. a -> Maybe a
Prelude.Just (Key
"snapshotName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
snapshotName)
          ]
      )

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

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

-- | /See:/ 'newCreateSnapshotResponse' smart constructor.
data CreateSnapshotResponse = CreateSnapshotResponse'
  { -- | The created snapshot object.
    CreateSnapshotResponse -> Maybe Snapshot
snapshot :: Prelude.Maybe Snapshot,
    -- | The response's http status code.
    CreateSnapshotResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (CreateSnapshotResponse -> CreateSnapshotResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateSnapshotResponse -> CreateSnapshotResponse -> Bool
$c/= :: CreateSnapshotResponse -> CreateSnapshotResponse -> Bool
== :: CreateSnapshotResponse -> CreateSnapshotResponse -> Bool
$c== :: CreateSnapshotResponse -> CreateSnapshotResponse -> Bool
Prelude.Eq, ReadPrec [CreateSnapshotResponse]
ReadPrec CreateSnapshotResponse
Int -> ReadS CreateSnapshotResponse
ReadS [CreateSnapshotResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateSnapshotResponse]
$creadListPrec :: ReadPrec [CreateSnapshotResponse]
readPrec :: ReadPrec CreateSnapshotResponse
$creadPrec :: ReadPrec CreateSnapshotResponse
readList :: ReadS [CreateSnapshotResponse]
$creadList :: ReadS [CreateSnapshotResponse]
readsPrec :: Int -> ReadS CreateSnapshotResponse
$creadsPrec :: Int -> ReadS CreateSnapshotResponse
Prelude.Read, Int -> CreateSnapshotResponse -> ShowS
[CreateSnapshotResponse] -> ShowS
CreateSnapshotResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateSnapshotResponse] -> ShowS
$cshowList :: [CreateSnapshotResponse] -> ShowS
show :: CreateSnapshotResponse -> String
$cshow :: CreateSnapshotResponse -> String
showsPrec :: Int -> CreateSnapshotResponse -> ShowS
$cshowsPrec :: Int -> CreateSnapshotResponse -> ShowS
Prelude.Show, forall x. Rep CreateSnapshotResponse x -> CreateSnapshotResponse
forall x. CreateSnapshotResponse -> Rep CreateSnapshotResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateSnapshotResponse x -> CreateSnapshotResponse
$cfrom :: forall x. CreateSnapshotResponse -> Rep CreateSnapshotResponse x
Prelude.Generic)

-- |
-- Create a value of 'CreateSnapshotResponse' 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:
--
-- 'snapshot', 'createSnapshotResponse_snapshot' - The created snapshot object.
--
-- 'httpStatus', 'createSnapshotResponse_httpStatus' - The response's http status code.
newCreateSnapshotResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  CreateSnapshotResponse
newCreateSnapshotResponse :: Int -> CreateSnapshotResponse
newCreateSnapshotResponse Int
pHttpStatus_ =
  CreateSnapshotResponse'
    { $sel:snapshot:CreateSnapshotResponse' :: Maybe Snapshot
snapshot = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:CreateSnapshotResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The created snapshot object.
createSnapshotResponse_snapshot :: Lens.Lens' CreateSnapshotResponse (Prelude.Maybe Snapshot)
createSnapshotResponse_snapshot :: Lens' CreateSnapshotResponse (Maybe Snapshot)
createSnapshotResponse_snapshot = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateSnapshotResponse' {Maybe Snapshot
snapshot :: Maybe Snapshot
$sel:snapshot:CreateSnapshotResponse' :: CreateSnapshotResponse -> Maybe Snapshot
snapshot} -> Maybe Snapshot
snapshot) (\s :: CreateSnapshotResponse
s@CreateSnapshotResponse' {} Maybe Snapshot
a -> CreateSnapshotResponse
s {$sel:snapshot:CreateSnapshotResponse' :: Maybe Snapshot
snapshot = Maybe Snapshot
a} :: CreateSnapshotResponse)

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

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