{-# 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.Nimble.GetStreamingSessionBackup
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Gets @StreamingSessionBackup@ resource.
--
-- Invoke this operation to poll for a streaming session backup while
-- stopping a streaming session.
module Amazonka.Nimble.GetStreamingSessionBackup
  ( -- * Creating a Request
    GetStreamingSessionBackup (..),
    newGetStreamingSessionBackup,

    -- * Request Lenses
    getStreamingSessionBackup_backupId,
    getStreamingSessionBackup_studioId,

    -- * Destructuring the Response
    GetStreamingSessionBackupResponse (..),
    newGetStreamingSessionBackupResponse,

    -- * Response Lenses
    getStreamingSessionBackupResponse_streamingSessionBackup,
    getStreamingSessionBackupResponse_httpStatus,
  )
where

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

-- | /See:/ 'newGetStreamingSessionBackup' smart constructor.
data GetStreamingSessionBackup = GetStreamingSessionBackup'
  { -- | The ID of the backup.
    GetStreamingSessionBackup -> Text
backupId :: Prelude.Text,
    -- | The studio ID.
    GetStreamingSessionBackup -> Text
studioId :: Prelude.Text
  }
  deriving (GetStreamingSessionBackup -> GetStreamingSessionBackup -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetStreamingSessionBackup -> GetStreamingSessionBackup -> Bool
$c/= :: GetStreamingSessionBackup -> GetStreamingSessionBackup -> Bool
== :: GetStreamingSessionBackup -> GetStreamingSessionBackup -> Bool
$c== :: GetStreamingSessionBackup -> GetStreamingSessionBackup -> Bool
Prelude.Eq, ReadPrec [GetStreamingSessionBackup]
ReadPrec GetStreamingSessionBackup
Int -> ReadS GetStreamingSessionBackup
ReadS [GetStreamingSessionBackup]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetStreamingSessionBackup]
$creadListPrec :: ReadPrec [GetStreamingSessionBackup]
readPrec :: ReadPrec GetStreamingSessionBackup
$creadPrec :: ReadPrec GetStreamingSessionBackup
readList :: ReadS [GetStreamingSessionBackup]
$creadList :: ReadS [GetStreamingSessionBackup]
readsPrec :: Int -> ReadS GetStreamingSessionBackup
$creadsPrec :: Int -> ReadS GetStreamingSessionBackup
Prelude.Read, Int -> GetStreamingSessionBackup -> ShowS
[GetStreamingSessionBackup] -> ShowS
GetStreamingSessionBackup -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetStreamingSessionBackup] -> ShowS
$cshowList :: [GetStreamingSessionBackup] -> ShowS
show :: GetStreamingSessionBackup -> String
$cshow :: GetStreamingSessionBackup -> String
showsPrec :: Int -> GetStreamingSessionBackup -> ShowS
$cshowsPrec :: Int -> GetStreamingSessionBackup -> ShowS
Prelude.Show, forall x.
Rep GetStreamingSessionBackup x -> GetStreamingSessionBackup
forall x.
GetStreamingSessionBackup -> Rep GetStreamingSessionBackup x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetStreamingSessionBackup x -> GetStreamingSessionBackup
$cfrom :: forall x.
GetStreamingSessionBackup -> Rep GetStreamingSessionBackup x
Prelude.Generic)

-- |
-- Create a value of 'GetStreamingSessionBackup' 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:
--
-- 'backupId', 'getStreamingSessionBackup_backupId' - The ID of the backup.
--
-- 'studioId', 'getStreamingSessionBackup_studioId' - The studio ID.
newGetStreamingSessionBackup ::
  -- | 'backupId'
  Prelude.Text ->
  -- | 'studioId'
  Prelude.Text ->
  GetStreamingSessionBackup
newGetStreamingSessionBackup :: Text -> Text -> GetStreamingSessionBackup
newGetStreamingSessionBackup Text
pBackupId_ Text
pStudioId_ =
  GetStreamingSessionBackup'
    { $sel:backupId:GetStreamingSessionBackup' :: Text
backupId = Text
pBackupId_,
      $sel:studioId:GetStreamingSessionBackup' :: Text
studioId = Text
pStudioId_
    }

-- | The ID of the backup.
getStreamingSessionBackup_backupId :: Lens.Lens' GetStreamingSessionBackup Prelude.Text
getStreamingSessionBackup_backupId :: Lens' GetStreamingSessionBackup Text
getStreamingSessionBackup_backupId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetStreamingSessionBackup' {Text
backupId :: Text
$sel:backupId:GetStreamingSessionBackup' :: GetStreamingSessionBackup -> Text
backupId} -> Text
backupId) (\s :: GetStreamingSessionBackup
s@GetStreamingSessionBackup' {} Text
a -> GetStreamingSessionBackup
s {$sel:backupId:GetStreamingSessionBackup' :: Text
backupId = Text
a} :: GetStreamingSessionBackup)

-- | The studio ID.
getStreamingSessionBackup_studioId :: Lens.Lens' GetStreamingSessionBackup Prelude.Text
getStreamingSessionBackup_studioId :: Lens' GetStreamingSessionBackup Text
getStreamingSessionBackup_studioId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetStreamingSessionBackup' {Text
studioId :: Text
$sel:studioId:GetStreamingSessionBackup' :: GetStreamingSessionBackup -> Text
studioId} -> Text
studioId) (\s :: GetStreamingSessionBackup
s@GetStreamingSessionBackup' {} Text
a -> GetStreamingSessionBackup
s {$sel:studioId:GetStreamingSessionBackup' :: Text
studioId = Text
a} :: GetStreamingSessionBackup)

instance Core.AWSRequest GetStreamingSessionBackup where
  type
    AWSResponse GetStreamingSessionBackup =
      GetStreamingSessionBackupResponse
  request :: (Service -> Service)
-> GetStreamingSessionBackup -> Request GetStreamingSessionBackup
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.get (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy GetStreamingSessionBackup
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse GetStreamingSessionBackup)))
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 StreamingSessionBackup
-> Int -> GetStreamingSessionBackupResponse
GetStreamingSessionBackupResponse'
            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
"streamingSessionBackup")
            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 GetStreamingSessionBackup where
  hashWithSalt :: Int -> GetStreamingSessionBackup -> Int
hashWithSalt Int
_salt GetStreamingSessionBackup' {Text
studioId :: Text
backupId :: Text
$sel:studioId:GetStreamingSessionBackup' :: GetStreamingSessionBackup -> Text
$sel:backupId:GetStreamingSessionBackup' :: GetStreamingSessionBackup -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
backupId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
studioId

instance Prelude.NFData GetStreamingSessionBackup where
  rnf :: GetStreamingSessionBackup -> ()
rnf GetStreamingSessionBackup' {Text
studioId :: Text
backupId :: Text
$sel:studioId:GetStreamingSessionBackup' :: GetStreamingSessionBackup -> Text
$sel:backupId:GetStreamingSessionBackup' :: GetStreamingSessionBackup -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
backupId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
studioId

instance Data.ToHeaders GetStreamingSessionBackup where
  toHeaders :: GetStreamingSessionBackup -> 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.ToPath GetStreamingSessionBackup where
  toPath :: GetStreamingSessionBackup -> ByteString
toPath GetStreamingSessionBackup' {Text
studioId :: Text
backupId :: Text
$sel:studioId:GetStreamingSessionBackup' :: GetStreamingSessionBackup -> Text
$sel:backupId:GetStreamingSessionBackup' :: GetStreamingSessionBackup -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/2020-08-01/studios/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
studioId,
        ByteString
"/streaming-session-backups/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
backupId
      ]

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

-- | /See:/ 'newGetStreamingSessionBackupResponse' smart constructor.
data GetStreamingSessionBackupResponse = GetStreamingSessionBackupResponse'
  { -- | Information about the streaming session backup.
    GetStreamingSessionBackupResponse -> Maybe StreamingSessionBackup
streamingSessionBackup :: Prelude.Maybe StreamingSessionBackup,
    -- | The response's http status code.
    GetStreamingSessionBackupResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetStreamingSessionBackupResponse
-> GetStreamingSessionBackupResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetStreamingSessionBackupResponse
-> GetStreamingSessionBackupResponse -> Bool
$c/= :: GetStreamingSessionBackupResponse
-> GetStreamingSessionBackupResponse -> Bool
== :: GetStreamingSessionBackupResponse
-> GetStreamingSessionBackupResponse -> Bool
$c== :: GetStreamingSessionBackupResponse
-> GetStreamingSessionBackupResponse -> Bool
Prelude.Eq, ReadPrec [GetStreamingSessionBackupResponse]
ReadPrec GetStreamingSessionBackupResponse
Int -> ReadS GetStreamingSessionBackupResponse
ReadS [GetStreamingSessionBackupResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetStreamingSessionBackupResponse]
$creadListPrec :: ReadPrec [GetStreamingSessionBackupResponse]
readPrec :: ReadPrec GetStreamingSessionBackupResponse
$creadPrec :: ReadPrec GetStreamingSessionBackupResponse
readList :: ReadS [GetStreamingSessionBackupResponse]
$creadList :: ReadS [GetStreamingSessionBackupResponse]
readsPrec :: Int -> ReadS GetStreamingSessionBackupResponse
$creadsPrec :: Int -> ReadS GetStreamingSessionBackupResponse
Prelude.Read, Int -> GetStreamingSessionBackupResponse -> ShowS
[GetStreamingSessionBackupResponse] -> ShowS
GetStreamingSessionBackupResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetStreamingSessionBackupResponse] -> ShowS
$cshowList :: [GetStreamingSessionBackupResponse] -> ShowS
show :: GetStreamingSessionBackupResponse -> String
$cshow :: GetStreamingSessionBackupResponse -> String
showsPrec :: Int -> GetStreamingSessionBackupResponse -> ShowS
$cshowsPrec :: Int -> GetStreamingSessionBackupResponse -> ShowS
Prelude.Show, forall x.
Rep GetStreamingSessionBackupResponse x
-> GetStreamingSessionBackupResponse
forall x.
GetStreamingSessionBackupResponse
-> Rep GetStreamingSessionBackupResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetStreamingSessionBackupResponse x
-> GetStreamingSessionBackupResponse
$cfrom :: forall x.
GetStreamingSessionBackupResponse
-> Rep GetStreamingSessionBackupResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetStreamingSessionBackupResponse' 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:
--
-- 'streamingSessionBackup', 'getStreamingSessionBackupResponse_streamingSessionBackup' - Information about the streaming session backup.
--
-- 'httpStatus', 'getStreamingSessionBackupResponse_httpStatus' - The response's http status code.
newGetStreamingSessionBackupResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetStreamingSessionBackupResponse
newGetStreamingSessionBackupResponse :: Int -> GetStreamingSessionBackupResponse
newGetStreamingSessionBackupResponse Int
pHttpStatus_ =
  GetStreamingSessionBackupResponse'
    { $sel:streamingSessionBackup:GetStreamingSessionBackupResponse' :: Maybe StreamingSessionBackup
streamingSessionBackup =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetStreamingSessionBackupResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Information about the streaming session backup.
getStreamingSessionBackupResponse_streamingSessionBackup :: Lens.Lens' GetStreamingSessionBackupResponse (Prelude.Maybe StreamingSessionBackup)
getStreamingSessionBackupResponse_streamingSessionBackup :: Lens'
  GetStreamingSessionBackupResponse (Maybe StreamingSessionBackup)
getStreamingSessionBackupResponse_streamingSessionBackup = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetStreamingSessionBackupResponse' {Maybe StreamingSessionBackup
streamingSessionBackup :: Maybe StreamingSessionBackup
$sel:streamingSessionBackup:GetStreamingSessionBackupResponse' :: GetStreamingSessionBackupResponse -> Maybe StreamingSessionBackup
streamingSessionBackup} -> Maybe StreamingSessionBackup
streamingSessionBackup) (\s :: GetStreamingSessionBackupResponse
s@GetStreamingSessionBackupResponse' {} Maybe StreamingSessionBackup
a -> GetStreamingSessionBackupResponse
s {$sel:streamingSessionBackup:GetStreamingSessionBackupResponse' :: Maybe StreamingSessionBackup
streamingSessionBackup = Maybe StreamingSessionBackup
a} :: GetStreamingSessionBackupResponse)

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

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