{-# 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.RolesAnywhere.GetSubject
-- 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 a Subject. A Subject associates a certificate identity with
-- authentication attempts by CreateSession. The Subject resources stores
-- audit information such as status of the last authentication attempt, the
-- certificate data used in the attempt, and the last time the associated
-- identity attempted authentication.
--
-- __Required permissions:__ @rolesanywhere:GetSubject@.
module Amazonka.RolesAnywhere.GetSubject
  ( -- * Creating a Request
    GetSubject (..),
    newGetSubject,

    -- * Request Lenses
    getSubject_subjectId,

    -- * Destructuring the Response
    GetSubjectResponse (..),
    newGetSubjectResponse,

    -- * Response Lenses
    getSubjectResponse_subject,
    getSubjectResponse_httpStatus,
  )
where

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

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

-- |
-- Create a value of 'GetSubject' 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:
--
-- 'subjectId', 'getSubject_subjectId' - The unique identifier of the subject.
newGetSubject ::
  -- | 'subjectId'
  Prelude.Text ->
  GetSubject
newGetSubject :: Text -> GetSubject
newGetSubject Text
pSubjectId_ =
  GetSubject' {$sel:subjectId:GetSubject' :: Text
subjectId = Text
pSubjectId_}

-- | The unique identifier of the subject.
getSubject_subjectId :: Lens.Lens' GetSubject Prelude.Text
getSubject_subjectId :: Lens' GetSubject Text
getSubject_subjectId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetSubject' {Text
subjectId :: Text
$sel:subjectId:GetSubject' :: GetSubject -> Text
subjectId} -> Text
subjectId) (\s :: GetSubject
s@GetSubject' {} Text
a -> GetSubject
s {$sel:subjectId:GetSubject' :: Text
subjectId = Text
a} :: GetSubject)

instance Core.AWSRequest GetSubject where
  type AWSResponse GetSubject = GetSubjectResponse
  request :: (Service -> Service) -> GetSubject -> Request GetSubject
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 GetSubject
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse GetSubject)))
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 SubjectDetail -> Int -> GetSubjectResponse
GetSubjectResponse'
            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
"subject")
            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 GetSubject where
  hashWithSalt :: Int -> GetSubject -> Int
hashWithSalt Int
_salt GetSubject' {Text
subjectId :: Text
$sel:subjectId:GetSubject' :: GetSubject -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
subjectId

instance Prelude.NFData GetSubject where
  rnf :: GetSubject -> ()
rnf GetSubject' {Text
subjectId :: Text
$sel:subjectId:GetSubject' :: GetSubject -> Text
..} = forall a. NFData a => a -> ()
Prelude.rnf Text
subjectId

instance Data.ToHeaders GetSubject where
  toHeaders :: GetSubject -> 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 GetSubject where
  toPath :: GetSubject -> ByteString
toPath GetSubject' {Text
subjectId :: Text
$sel:subjectId:GetSubject' :: GetSubject -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat [ByteString
"/subject/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
subjectId]

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

-- | /See:/ 'newGetSubjectResponse' smart constructor.
data GetSubjectResponse = GetSubjectResponse'
  { -- | The state of the subject after a read or write operation.
    GetSubjectResponse -> Maybe SubjectDetail
subject :: Prelude.Maybe SubjectDetail,
    -- | The response's http status code.
    GetSubjectResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetSubjectResponse -> GetSubjectResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetSubjectResponse -> GetSubjectResponse -> Bool
$c/= :: GetSubjectResponse -> GetSubjectResponse -> Bool
== :: GetSubjectResponse -> GetSubjectResponse -> Bool
$c== :: GetSubjectResponse -> GetSubjectResponse -> Bool
Prelude.Eq, ReadPrec [GetSubjectResponse]
ReadPrec GetSubjectResponse
Int -> ReadS GetSubjectResponse
ReadS [GetSubjectResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetSubjectResponse]
$creadListPrec :: ReadPrec [GetSubjectResponse]
readPrec :: ReadPrec GetSubjectResponse
$creadPrec :: ReadPrec GetSubjectResponse
readList :: ReadS [GetSubjectResponse]
$creadList :: ReadS [GetSubjectResponse]
readsPrec :: Int -> ReadS GetSubjectResponse
$creadsPrec :: Int -> ReadS GetSubjectResponse
Prelude.Read, Int -> GetSubjectResponse -> ShowS
[GetSubjectResponse] -> ShowS
GetSubjectResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetSubjectResponse] -> ShowS
$cshowList :: [GetSubjectResponse] -> ShowS
show :: GetSubjectResponse -> String
$cshow :: GetSubjectResponse -> String
showsPrec :: Int -> GetSubjectResponse -> ShowS
$cshowsPrec :: Int -> GetSubjectResponse -> ShowS
Prelude.Show, forall x. Rep GetSubjectResponse x -> GetSubjectResponse
forall x. GetSubjectResponse -> Rep GetSubjectResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetSubjectResponse x -> GetSubjectResponse
$cfrom :: forall x. GetSubjectResponse -> Rep GetSubjectResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetSubjectResponse' 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:
--
-- 'subject', 'getSubjectResponse_subject' - The state of the subject after a read or write operation.
--
-- 'httpStatus', 'getSubjectResponse_httpStatus' - The response's http status code.
newGetSubjectResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetSubjectResponse
newGetSubjectResponse :: Int -> GetSubjectResponse
newGetSubjectResponse Int
pHttpStatus_ =
  GetSubjectResponse'
    { $sel:subject:GetSubjectResponse' :: Maybe SubjectDetail
subject = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetSubjectResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The state of the subject after a read or write operation.
getSubjectResponse_subject :: Lens.Lens' GetSubjectResponse (Prelude.Maybe SubjectDetail)
getSubjectResponse_subject :: Lens' GetSubjectResponse (Maybe SubjectDetail)
getSubjectResponse_subject = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetSubjectResponse' {Maybe SubjectDetail
subject :: Maybe SubjectDetail
$sel:subject:GetSubjectResponse' :: GetSubjectResponse -> Maybe SubjectDetail
subject} -> Maybe SubjectDetail
subject) (\s :: GetSubjectResponse
s@GetSubjectResponse' {} Maybe SubjectDetail
a -> GetSubjectResponse
s {$sel:subject:GetSubjectResponse' :: Maybe SubjectDetail
subject = Maybe SubjectDetail
a} :: GetSubjectResponse)

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

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