{-# 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.Glue.StopSession
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Stops the session.
module Amazonka.Glue.StopSession
  ( -- * Creating a Request
    StopSession (..),
    newStopSession,

    -- * Request Lenses
    stopSession_requestOrigin,
    stopSession_id,

    -- * Destructuring the Response
    StopSessionResponse (..),
    newStopSessionResponse,

    -- * Response Lenses
    stopSessionResponse_id,
    stopSessionResponse_httpStatus,
  )
where

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

-- | /See:/ 'newStopSession' smart constructor.
data StopSession = StopSession'
  { -- | The origin of the request.
    StopSession -> Maybe Text
requestOrigin :: Prelude.Maybe Prelude.Text,
    -- | The ID of the session to be stopped.
    StopSession -> Text
id :: Prelude.Text
  }
  deriving (StopSession -> StopSession -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StopSession -> StopSession -> Bool
$c/= :: StopSession -> StopSession -> Bool
== :: StopSession -> StopSession -> Bool
$c== :: StopSession -> StopSession -> Bool
Prelude.Eq, ReadPrec [StopSession]
ReadPrec StopSession
Int -> ReadS StopSession
ReadS [StopSession]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [StopSession]
$creadListPrec :: ReadPrec [StopSession]
readPrec :: ReadPrec StopSession
$creadPrec :: ReadPrec StopSession
readList :: ReadS [StopSession]
$creadList :: ReadS [StopSession]
readsPrec :: Int -> ReadS StopSession
$creadsPrec :: Int -> ReadS StopSession
Prelude.Read, Int -> StopSession -> ShowS
[StopSession] -> ShowS
StopSession -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StopSession] -> ShowS
$cshowList :: [StopSession] -> ShowS
show :: StopSession -> String
$cshow :: StopSession -> String
showsPrec :: Int -> StopSession -> ShowS
$cshowsPrec :: Int -> StopSession -> ShowS
Prelude.Show, forall x. Rep StopSession x -> StopSession
forall x. StopSession -> Rep StopSession x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep StopSession x -> StopSession
$cfrom :: forall x. StopSession -> Rep StopSession x
Prelude.Generic)

-- |
-- Create a value of 'StopSession' 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:
--
-- 'requestOrigin', 'stopSession_requestOrigin' - The origin of the request.
--
-- 'id', 'stopSession_id' - The ID of the session to be stopped.
newStopSession ::
  -- | 'id'
  Prelude.Text ->
  StopSession
newStopSession :: Text -> StopSession
newStopSession Text
pId_ =
  StopSession'
    { $sel:requestOrigin:StopSession' :: Maybe Text
requestOrigin = forall a. Maybe a
Prelude.Nothing,
      $sel:id:StopSession' :: Text
id = Text
pId_
    }

-- | The origin of the request.
stopSession_requestOrigin :: Lens.Lens' StopSession (Prelude.Maybe Prelude.Text)
stopSession_requestOrigin :: Lens' StopSession (Maybe Text)
stopSession_requestOrigin = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StopSession' {Maybe Text
requestOrigin :: Maybe Text
$sel:requestOrigin:StopSession' :: StopSession -> Maybe Text
requestOrigin} -> Maybe Text
requestOrigin) (\s :: StopSession
s@StopSession' {} Maybe Text
a -> StopSession
s {$sel:requestOrigin:StopSession' :: Maybe Text
requestOrigin = Maybe Text
a} :: StopSession)

-- | The ID of the session to be stopped.
stopSession_id :: Lens.Lens' StopSession Prelude.Text
stopSession_id :: Lens' StopSession Text
stopSession_id = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StopSession' {Text
id :: Text
$sel:id:StopSession' :: StopSession -> Text
id} -> Text
id) (\s :: StopSession
s@StopSession' {} Text
a -> StopSession
s {$sel:id:StopSession' :: Text
id = Text
a} :: StopSession)

instance Core.AWSRequest StopSession where
  type AWSResponse StopSession = StopSessionResponse
  request :: (Service -> Service) -> StopSession -> Request StopSession
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 StopSession
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse StopSession)))
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 -> StopSessionResponse
StopSessionResponse'
            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
"Id")
            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 StopSession where
  hashWithSalt :: Int -> StopSession -> Int
hashWithSalt Int
_salt StopSession' {Maybe Text
Text
id :: Text
requestOrigin :: Maybe Text
$sel:id:StopSession' :: StopSession -> Text
$sel:requestOrigin:StopSession' :: StopSession -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
requestOrigin
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
id

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

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

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

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

-- | /See:/ 'newStopSessionResponse' smart constructor.
data StopSessionResponse = StopSessionResponse'
  { -- | Returns the Id of the stopped session.
    StopSessionResponse -> Maybe Text
id :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    StopSessionResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (StopSessionResponse -> StopSessionResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StopSessionResponse -> StopSessionResponse -> Bool
$c/= :: StopSessionResponse -> StopSessionResponse -> Bool
== :: StopSessionResponse -> StopSessionResponse -> Bool
$c== :: StopSessionResponse -> StopSessionResponse -> Bool
Prelude.Eq, ReadPrec [StopSessionResponse]
ReadPrec StopSessionResponse
Int -> ReadS StopSessionResponse
ReadS [StopSessionResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [StopSessionResponse]
$creadListPrec :: ReadPrec [StopSessionResponse]
readPrec :: ReadPrec StopSessionResponse
$creadPrec :: ReadPrec StopSessionResponse
readList :: ReadS [StopSessionResponse]
$creadList :: ReadS [StopSessionResponse]
readsPrec :: Int -> ReadS StopSessionResponse
$creadsPrec :: Int -> ReadS StopSessionResponse
Prelude.Read, Int -> StopSessionResponse -> ShowS
[StopSessionResponse] -> ShowS
StopSessionResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StopSessionResponse] -> ShowS
$cshowList :: [StopSessionResponse] -> ShowS
show :: StopSessionResponse -> String
$cshow :: StopSessionResponse -> String
showsPrec :: Int -> StopSessionResponse -> ShowS
$cshowsPrec :: Int -> StopSessionResponse -> ShowS
Prelude.Show, forall x. Rep StopSessionResponse x -> StopSessionResponse
forall x. StopSessionResponse -> Rep StopSessionResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep StopSessionResponse x -> StopSessionResponse
$cfrom :: forall x. StopSessionResponse -> Rep StopSessionResponse x
Prelude.Generic)

-- |
-- Create a value of 'StopSessionResponse' 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:
--
-- 'id', 'stopSessionResponse_id' - Returns the Id of the stopped session.
--
-- 'httpStatus', 'stopSessionResponse_httpStatus' - The response's http status code.
newStopSessionResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  StopSessionResponse
newStopSessionResponse :: Int -> StopSessionResponse
newStopSessionResponse Int
pHttpStatus_ =
  StopSessionResponse'
    { $sel:id:StopSessionResponse' :: Maybe Text
id = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:StopSessionResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Returns the Id of the stopped session.
stopSessionResponse_id :: Lens.Lens' StopSessionResponse (Prelude.Maybe Prelude.Text)
stopSessionResponse_id :: Lens' StopSessionResponse (Maybe Text)
stopSessionResponse_id = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StopSessionResponse' {Maybe Text
id :: Maybe Text
$sel:id:StopSessionResponse' :: StopSessionResponse -> Maybe Text
id} -> Maybe Text
id) (\s :: StopSessionResponse
s@StopSessionResponse' {} Maybe Text
a -> StopSessionResponse
s {$sel:id:StopSessionResponse' :: Maybe Text
id = Maybe Text
a} :: StopSessionResponse)

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

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