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

    -- * Request Lenses
    getSession_requestOrigin,
    getSession_id,

    -- * Destructuring the Response
    GetSessionResponse (..),
    newGetSessionResponse,

    -- * Response Lenses
    getSessionResponse_session,
    getSessionResponse_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:/ 'newGetSession' smart constructor.
data GetSession = GetSession'
  { -- | The origin of the request.
    GetSession -> Maybe Text
requestOrigin :: Prelude.Maybe Prelude.Text,
    -- | The ID of the session.
    GetSession -> Text
id :: Prelude.Text
  }
  deriving (GetSession -> GetSession -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetSession -> GetSession -> Bool
$c/= :: GetSession -> GetSession -> Bool
== :: GetSession -> GetSession -> Bool
$c== :: GetSession -> GetSession -> Bool
Prelude.Eq, ReadPrec [GetSession]
ReadPrec GetSession
Int -> ReadS GetSession
ReadS [GetSession]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetSession]
$creadListPrec :: ReadPrec [GetSession]
readPrec :: ReadPrec GetSession
$creadPrec :: ReadPrec GetSession
readList :: ReadS [GetSession]
$creadList :: ReadS [GetSession]
readsPrec :: Int -> ReadS GetSession
$creadsPrec :: Int -> ReadS GetSession
Prelude.Read, Int -> GetSession -> ShowS
[GetSession] -> ShowS
GetSession -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetSession] -> ShowS
$cshowList :: [GetSession] -> ShowS
show :: GetSession -> String
$cshow :: GetSession -> String
showsPrec :: Int -> GetSession -> ShowS
$cshowsPrec :: Int -> GetSession -> ShowS
Prelude.Show, forall x. Rep GetSession x -> GetSession
forall x. GetSession -> Rep GetSession x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetSession x -> GetSession
$cfrom :: forall x. GetSession -> Rep GetSession x
Prelude.Generic)

-- |
-- Create a value of 'GetSession' 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', 'getSession_requestOrigin' - The origin of the request.
--
-- 'id', 'getSession_id' - The ID of the session.
newGetSession ::
  -- | 'id'
  Prelude.Text ->
  GetSession
newGetSession :: Text -> GetSession
newGetSession Text
pId_ =
  GetSession'
    { $sel:requestOrigin:GetSession' :: Maybe Text
requestOrigin = forall a. Maybe a
Prelude.Nothing,
      $sel:id:GetSession' :: Text
id = Text
pId_
    }

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

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

instance Core.AWSRequest GetSession where
  type AWSResponse GetSession = GetSessionResponse
  request :: (Service -> Service) -> GetSession -> Request GetSession
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 GetSession
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse GetSession)))
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 Session -> Int -> GetSessionResponse
GetSessionResponse'
            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
"Session")
            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 GetSession where
  hashWithSalt :: Int -> GetSession -> Int
hashWithSalt Int
_salt GetSession' {Maybe Text
Text
id :: Text
requestOrigin :: Maybe Text
$sel:id:GetSession' :: GetSession -> Text
$sel:requestOrigin:GetSession' :: GetSession -> 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 GetSession where
  rnf :: GetSession -> ()
rnf GetSession' {Maybe Text
Text
id :: Text
requestOrigin :: Maybe Text
$sel:id:GetSession' :: GetSession -> Text
$sel:requestOrigin:GetSession' :: GetSession -> 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 GetSession where
  toHeaders :: GetSession -> 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.GetSession" :: 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 GetSession where
  toJSON :: GetSession -> Value
toJSON GetSession' {Maybe Text
Text
id :: Text
requestOrigin :: Maybe Text
$sel:id:GetSession' :: GetSession -> Text
$sel:requestOrigin:GetSession' :: GetSession -> 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 GetSession where
  toPath :: GetSession -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

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

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

-- |
-- Create a value of 'GetSessionResponse' 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:
--
-- 'session', 'getSessionResponse_session' - The session object is returned in the response.
--
-- 'httpStatus', 'getSessionResponse_httpStatus' - The response's http status code.
newGetSessionResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetSessionResponse
newGetSessionResponse :: Int -> GetSessionResponse
newGetSessionResponse Int
pHttpStatus_ =
  GetSessionResponse'
    { $sel:session:GetSessionResponse' :: Maybe Session
session = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetSessionResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The session object is returned in the response.
getSessionResponse_session :: Lens.Lens' GetSessionResponse (Prelude.Maybe Session)
getSessionResponse_session :: Lens' GetSessionResponse (Maybe Session)
getSessionResponse_session = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetSessionResponse' {Maybe Session
session :: Maybe Session
$sel:session:GetSessionResponse' :: GetSessionResponse -> Maybe Session
session} -> Maybe Session
session) (\s :: GetSessionResponse
s@GetSessionResponse' {} Maybe Session
a -> GetSessionResponse
s {$sel:session:GetSessionResponse' :: Maybe Session
session = Maybe Session
a} :: GetSessionResponse)

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

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