{-# 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.FSx.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 an existing Amazon FSx for OpenZFS volume. With
-- snapshots, you can easily undo file changes and compare file versions by
-- restoring the volume to a previous version.
--
-- If a snapshot with the specified client request token exists, and the
-- parameters match, this operation returns the description of the existing
-- snapshot. If a snapshot with the specified client request token exists,
-- and the parameters don\'t match, this operation returns
-- @IncompatibleParameterError@. If a snapshot with the specified client
-- request token doesn\'t exist, @CreateSnapshot@ does the following:
--
-- -   Creates a new OpenZFS snapshot with an assigned ID, and an initial
--     lifecycle state of @CREATING@.
--
-- -   Returns the description of the snapshot.
--
-- By using the idempotent operation, you can retry a @CreateSnapshot@
-- operation without the risk of creating an extra snapshot. This approach
-- can be useful when an initial call fails in a way that makes it unclear
-- whether a snapshot was created. If you use the same client request token
-- and the initial call created a snapshot, the operation returns a
-- successful result because all the parameters are the same.
--
-- The @CreateSnapshot@ operation returns while the snapshot\'s lifecycle
-- state is still @CREATING@. You can check the snapshot creation status by
-- calling the
-- <https://docs.aws.amazon.com/fsx/latest/APIReference/API_DescribeSnapshots.html DescribeSnapshots>
-- operation, which returns the snapshot state along with other
-- information.
module Amazonka.FSx.CreateSnapshot
  ( -- * Creating a Request
    CreateSnapshot (..),
    newCreateSnapshot,

    -- * Request Lenses
    createSnapshot_clientRequestToken,
    createSnapshot_tags,
    createSnapshot_name,
    createSnapshot_volumeId,

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

-- | /See:/ 'newCreateSnapshot' smart constructor.
data CreateSnapshot = CreateSnapshot'
  { CreateSnapshot -> Maybe Text
clientRequestToken :: Prelude.Maybe Prelude.Text,
    CreateSnapshot -> Maybe (NonEmpty Tag)
tags :: Prelude.Maybe (Prelude.NonEmpty Tag),
    -- | The name of the snapshot.
    CreateSnapshot -> Text
name :: Prelude.Text,
    -- | The ID of the volume that you are taking a snapshot of.
    CreateSnapshot -> Text
volumeId :: 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:
--
-- 'clientRequestToken', 'createSnapshot_clientRequestToken' - Undocumented member.
--
-- 'tags', 'createSnapshot_tags' - Undocumented member.
--
-- 'name', 'createSnapshot_name' - The name of the snapshot.
--
-- 'volumeId', 'createSnapshot_volumeId' - The ID of the volume that you are taking a snapshot of.
newCreateSnapshot ::
  -- | 'name'
  Prelude.Text ->
  -- | 'volumeId'
  Prelude.Text ->
  CreateSnapshot
newCreateSnapshot :: Text -> Text -> CreateSnapshot
newCreateSnapshot Text
pName_ Text
pVolumeId_ =
  CreateSnapshot'
    { $sel:clientRequestToken:CreateSnapshot' :: Maybe Text
clientRequestToken =
        forall a. Maybe a
Prelude.Nothing,
      $sel:tags:CreateSnapshot' :: Maybe (NonEmpty Tag)
tags = forall a. Maybe a
Prelude.Nothing,
      $sel:name:CreateSnapshot' :: Text
name = Text
pName_,
      $sel:volumeId:CreateSnapshot' :: Text
volumeId = Text
pVolumeId_
    }

-- | Undocumented member.
createSnapshot_clientRequestToken :: Lens.Lens' CreateSnapshot (Prelude.Maybe Prelude.Text)
createSnapshot_clientRequestToken :: Lens' CreateSnapshot (Maybe Text)
createSnapshot_clientRequestToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateSnapshot' {Maybe Text
clientRequestToken :: Maybe Text
$sel:clientRequestToken:CreateSnapshot' :: CreateSnapshot -> Maybe Text
clientRequestToken} -> Maybe Text
clientRequestToken) (\s :: CreateSnapshot
s@CreateSnapshot' {} Maybe Text
a -> CreateSnapshot
s {$sel:clientRequestToken:CreateSnapshot' :: Maybe Text
clientRequestToken = Maybe Text
a} :: CreateSnapshot)

-- | Undocumented member.
createSnapshot_tags :: Lens.Lens' CreateSnapshot (Prelude.Maybe (Prelude.NonEmpty Tag))
createSnapshot_tags :: Lens' CreateSnapshot (Maybe (NonEmpty Tag))
createSnapshot_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateSnapshot' {Maybe (NonEmpty Tag)
tags :: Maybe (NonEmpty Tag)
$sel:tags:CreateSnapshot' :: CreateSnapshot -> Maybe (NonEmpty Tag)
tags} -> Maybe (NonEmpty Tag)
tags) (\s :: CreateSnapshot
s@CreateSnapshot' {} Maybe (NonEmpty Tag)
a -> CreateSnapshot
s {$sel:tags:CreateSnapshot' :: Maybe (NonEmpty Tag)
tags = Maybe (NonEmpty 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 name of the snapshot.
createSnapshot_name :: Lens.Lens' CreateSnapshot Prelude.Text
createSnapshot_name :: Lens' CreateSnapshot Text
createSnapshot_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateSnapshot' {Text
name :: Text
$sel:name:CreateSnapshot' :: CreateSnapshot -> Text
name} -> Text
name) (\s :: CreateSnapshot
s@CreateSnapshot' {} Text
a -> CreateSnapshot
s {$sel:name:CreateSnapshot' :: Text
name = Text
a} :: CreateSnapshot)

-- | The ID of the volume that you are taking a snapshot of.
createSnapshot_volumeId :: Lens.Lens' CreateSnapshot Prelude.Text
createSnapshot_volumeId :: Lens' CreateSnapshot Text
createSnapshot_volumeId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateSnapshot' {Text
volumeId :: Text
$sel:volumeId:CreateSnapshot' :: CreateSnapshot -> Text
volumeId} -> Text
volumeId) (\s :: CreateSnapshot
s@CreateSnapshot' {} Text
a -> CreateSnapshot
s {$sel:volumeId:CreateSnapshot' :: Text
volumeId = 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 (NonEmpty Tag)
Maybe Text
Text
volumeId :: Text
name :: Text
tags :: Maybe (NonEmpty Tag)
clientRequestToken :: Maybe Text
$sel:volumeId:CreateSnapshot' :: CreateSnapshot -> Text
$sel:name:CreateSnapshot' :: CreateSnapshot -> Text
$sel:tags:CreateSnapshot' :: CreateSnapshot -> Maybe (NonEmpty Tag)
$sel:clientRequestToken:CreateSnapshot' :: CreateSnapshot -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
clientRequestToken
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (NonEmpty Tag)
tags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
name
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
volumeId

instance Prelude.NFData CreateSnapshot where
  rnf :: CreateSnapshot -> ()
rnf CreateSnapshot' {Maybe (NonEmpty Tag)
Maybe Text
Text
volumeId :: Text
name :: Text
tags :: Maybe (NonEmpty Tag)
clientRequestToken :: Maybe Text
$sel:volumeId:CreateSnapshot' :: CreateSnapshot -> Text
$sel:name:CreateSnapshot' :: CreateSnapshot -> Text
$sel:tags:CreateSnapshot' :: CreateSnapshot -> Maybe (NonEmpty Tag)
$sel:clientRequestToken:CreateSnapshot' :: CreateSnapshot -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
clientRequestToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (NonEmpty Tag)
tags
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
name
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
volumeId

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
"AWSSimbaAPIService_v20180301.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 (NonEmpty Tag)
Maybe Text
Text
volumeId :: Text
name :: Text
tags :: Maybe (NonEmpty Tag)
clientRequestToken :: Maybe Text
$sel:volumeId:CreateSnapshot' :: CreateSnapshot -> Text
$sel:name:CreateSnapshot' :: CreateSnapshot -> Text
$sel:tags:CreateSnapshot' :: CreateSnapshot -> Maybe (NonEmpty Tag)
$sel:clientRequestToken:CreateSnapshot' :: CreateSnapshot -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"ClientRequestToken" 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 Text
clientRequestToken,
            (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 (NonEmpty Tag)
tags,
            forall a. a -> Maybe a
Prelude.Just (Key
"Name" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
name),
            forall a. a -> Maybe a
Prelude.Just (Key
"VolumeId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
volumeId)
          ]
      )

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'
  { -- | A description of the snapshot.
    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' - A description of the snapshot.
--
-- '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_
    }

-- | A description of the snapshot.
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