{-# 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.GamesParks.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 the game configuration.
module Amazonka.GamesParks.CreateSnapshot
  ( -- * Creating a Request
    CreateSnapshot (..),
    newCreateSnapshot,

    -- * Request Lenses
    createSnapshot_description,
    createSnapshot_gameName,

    -- * 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.GamesParks.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'
  { -- | The description of the snapshot.
    CreateSnapshot -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    -- | The name of the game.
    CreateSnapshot -> Text
gameName :: 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:
--
-- 'description', 'createSnapshot_description' - The description of the snapshot.
--
-- 'gameName', 'createSnapshot_gameName' - The name of the game.
newCreateSnapshot ::
  -- | 'gameName'
  Prelude.Text ->
  CreateSnapshot
newCreateSnapshot :: Text -> CreateSnapshot
newCreateSnapshot Text
pGameName_ =
  CreateSnapshot'
    { $sel:description:CreateSnapshot' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
      $sel:gameName:CreateSnapshot' :: Text
gameName = Text
pGameName_
    }

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

-- | The name of the game.
createSnapshot_gameName :: Lens.Lens' CreateSnapshot Prelude.Text
createSnapshot_gameName :: Lens' CreateSnapshot Text
createSnapshot_gameName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateSnapshot' {Text
gameName :: Text
$sel:gameName:CreateSnapshot' :: CreateSnapshot -> Text
gameName} -> Text
gameName) (\s :: CreateSnapshot
s@CreateSnapshot' {} Text
a -> CreateSnapshot
s {$sel:gameName:CreateSnapshot' :: Text
gameName = 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 SnapshotDetails -> 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 Text
Text
gameName :: Text
description :: Maybe Text
$sel:gameName:CreateSnapshot' :: CreateSnapshot -> Text
$sel:description:CreateSnapshot' :: CreateSnapshot -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
description
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
gameName

instance Prelude.NFData CreateSnapshot where
  rnf :: CreateSnapshot -> ()
rnf CreateSnapshot' {Maybe Text
Text
gameName :: Text
description :: Maybe Text
$sel:gameName:CreateSnapshot' :: CreateSnapshot -> Text
$sel:description:CreateSnapshot' :: CreateSnapshot -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
description
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
gameName

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
"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 Text
Text
gameName :: Text
description :: Maybe Text
$sel:gameName:CreateSnapshot' :: CreateSnapshot -> Text
$sel:description:CreateSnapshot' :: CreateSnapshot -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [(Key
"Description" 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
description]
      )

instance Data.ToPath CreateSnapshot where
  toPath :: CreateSnapshot -> ByteString
toPath CreateSnapshot' {Maybe Text
Text
gameName :: Text
description :: Maybe Text
$sel:gameName:CreateSnapshot' :: CreateSnapshot -> Text
$sel:description:CreateSnapshot' :: CreateSnapshot -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ByteString
"/game/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
gameName, ByteString
"/snapshot"]

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'
  { -- | Properties that provide details of the created snapshot.
    CreateSnapshotResponse -> Maybe SnapshotDetails
snapshot :: Prelude.Maybe SnapshotDetails,
    -- | 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' - Properties that provide details of the created 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 SnapshotDetails
snapshot = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:CreateSnapshotResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Properties that provide details of the created snapshot.
createSnapshotResponse_snapshot :: Lens.Lens' CreateSnapshotResponse (Prelude.Maybe SnapshotDetails)
createSnapshotResponse_snapshot :: Lens' CreateSnapshotResponse (Maybe SnapshotDetails)
createSnapshotResponse_snapshot = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateSnapshotResponse' {Maybe SnapshotDetails
snapshot :: Maybe SnapshotDetails
$sel:snapshot:CreateSnapshotResponse' :: CreateSnapshotResponse -> Maybe SnapshotDetails
snapshot} -> Maybe SnapshotDetails
snapshot) (\s :: CreateSnapshotResponse
s@CreateSnapshotResponse' {} Maybe SnapshotDetails
a -> CreateSnapshotResponse
s {$sel:snapshot:CreateSnapshotResponse' :: Maybe SnapshotDetails
snapshot = Maybe SnapshotDetails
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 SnapshotDetails
httpStatus :: Int
snapshot :: Maybe SnapshotDetails
$sel:httpStatus:CreateSnapshotResponse' :: CreateSnapshotResponse -> Int
$sel:snapshot:CreateSnapshotResponse' :: CreateSnapshotResponse -> Maybe SnapshotDetails
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe SnapshotDetails
snapshot
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus