{-# 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 #-}
module Amazonka.STS.GetCallerIdentity
(
GetCallerIdentity (..),
newGetCallerIdentity,
GetCallerIdentityResponse (..),
newGetCallerIdentityResponse,
getCallerIdentityResponse_account,
getCallerIdentityResponse_arn,
getCallerIdentityResponse_userId,
getCallerIdentityResponse_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.STS.Types
data GetCallerIdentity = GetCallerIdentity'
{
}
deriving (GetCallerIdentity -> GetCallerIdentity -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetCallerIdentity -> GetCallerIdentity -> Bool
$c/= :: GetCallerIdentity -> GetCallerIdentity -> Bool
== :: GetCallerIdentity -> GetCallerIdentity -> Bool
$c== :: GetCallerIdentity -> GetCallerIdentity -> Bool
Prelude.Eq, ReadPrec [GetCallerIdentity]
ReadPrec GetCallerIdentity
Int -> ReadS GetCallerIdentity
ReadS [GetCallerIdentity]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetCallerIdentity]
$creadListPrec :: ReadPrec [GetCallerIdentity]
readPrec :: ReadPrec GetCallerIdentity
$creadPrec :: ReadPrec GetCallerIdentity
readList :: ReadS [GetCallerIdentity]
$creadList :: ReadS [GetCallerIdentity]
readsPrec :: Int -> ReadS GetCallerIdentity
$creadsPrec :: Int -> ReadS GetCallerIdentity
Prelude.Read, Int -> GetCallerIdentity -> ShowS
[GetCallerIdentity] -> ShowS
GetCallerIdentity -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetCallerIdentity] -> ShowS
$cshowList :: [GetCallerIdentity] -> ShowS
show :: GetCallerIdentity -> String
$cshow :: GetCallerIdentity -> String
showsPrec :: Int -> GetCallerIdentity -> ShowS
$cshowsPrec :: Int -> GetCallerIdentity -> ShowS
Prelude.Show, forall x. Rep GetCallerIdentity x -> GetCallerIdentity
forall x. GetCallerIdentity -> Rep GetCallerIdentity x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetCallerIdentity x -> GetCallerIdentity
$cfrom :: forall x. GetCallerIdentity -> Rep GetCallerIdentity x
Prelude.Generic)
newGetCallerIdentity ::
GetCallerIdentity
newGetCallerIdentity :: GetCallerIdentity
newGetCallerIdentity = GetCallerIdentity
GetCallerIdentity'
instance Core.AWSRequest GetCallerIdentity where
type
AWSResponse GetCallerIdentity =
GetCallerIdentityResponse
request :: (Service -> Service)
-> GetCallerIdentity -> Request GetCallerIdentity
request Service -> Service
overrides =
forall a. ToRequest a => Service -> a -> Request a
Request.postQuery (Service -> Service
overrides Service
defaultService)
response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy GetCallerIdentity
-> ClientResponse ClientBody
-> m (Either
Error (ClientResponse (AWSResponse GetCallerIdentity)))
response =
forall (m :: * -> *) a.
MonadResource m =>
Text
-> (Int
-> ResponseHeaders -> [Node] -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveXMLWrapper
Text
"GetCallerIdentityResult"
( \Int
s ResponseHeaders
h [Node]
x ->
Maybe Text
-> Maybe Text -> Maybe Text -> Int -> GetCallerIdentityResponse
GetCallerIdentityResponse'
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"Account")
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"Arn")
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"UserId")
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 GetCallerIdentity where
hashWithSalt :: Int -> GetCallerIdentity -> Int
hashWithSalt Int
_salt GetCallerIdentity
_ =
Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` ()
instance Prelude.NFData GetCallerIdentity where
rnf :: GetCallerIdentity -> ()
rnf GetCallerIdentity
_ = ()
instance Data.ToHeaders GetCallerIdentity where
toHeaders :: GetCallerIdentity -> ResponseHeaders
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty
instance Data.ToPath GetCallerIdentity where
toPath :: GetCallerIdentity -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"
instance Data.ToQuery GetCallerIdentity where
toQuery :: GetCallerIdentity -> QueryString
toQuery =
forall a b. a -> b -> a
Prelude.const
( forall a. Monoid a => [a] -> a
Prelude.mconcat
[ ByteString
"Action"
forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"GetCallerIdentity" :: Prelude.ByteString),
ByteString
"Version"
forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2011-06-15" :: Prelude.ByteString)
]
)
data GetCallerIdentityResponse = GetCallerIdentityResponse'
{
GetCallerIdentityResponse -> Maybe Text
account :: Prelude.Maybe Prelude.Text,
GetCallerIdentityResponse -> Maybe Text
arn :: Prelude.Maybe Prelude.Text,
GetCallerIdentityResponse -> Maybe Text
userId :: Prelude.Maybe Prelude.Text,
GetCallerIdentityResponse -> Int
httpStatus :: Prelude.Int
}
deriving (GetCallerIdentityResponse -> GetCallerIdentityResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetCallerIdentityResponse -> GetCallerIdentityResponse -> Bool
$c/= :: GetCallerIdentityResponse -> GetCallerIdentityResponse -> Bool
== :: GetCallerIdentityResponse -> GetCallerIdentityResponse -> Bool
$c== :: GetCallerIdentityResponse -> GetCallerIdentityResponse -> Bool
Prelude.Eq, ReadPrec [GetCallerIdentityResponse]
ReadPrec GetCallerIdentityResponse
Int -> ReadS GetCallerIdentityResponse
ReadS [GetCallerIdentityResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetCallerIdentityResponse]
$creadListPrec :: ReadPrec [GetCallerIdentityResponse]
readPrec :: ReadPrec GetCallerIdentityResponse
$creadPrec :: ReadPrec GetCallerIdentityResponse
readList :: ReadS [GetCallerIdentityResponse]
$creadList :: ReadS [GetCallerIdentityResponse]
readsPrec :: Int -> ReadS GetCallerIdentityResponse
$creadsPrec :: Int -> ReadS GetCallerIdentityResponse
Prelude.Read, Int -> GetCallerIdentityResponse -> ShowS
[GetCallerIdentityResponse] -> ShowS
GetCallerIdentityResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetCallerIdentityResponse] -> ShowS
$cshowList :: [GetCallerIdentityResponse] -> ShowS
show :: GetCallerIdentityResponse -> String
$cshow :: GetCallerIdentityResponse -> String
showsPrec :: Int -> GetCallerIdentityResponse -> ShowS
$cshowsPrec :: Int -> GetCallerIdentityResponse -> ShowS
Prelude.Show, forall x.
Rep GetCallerIdentityResponse x -> GetCallerIdentityResponse
forall x.
GetCallerIdentityResponse -> Rep GetCallerIdentityResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetCallerIdentityResponse x -> GetCallerIdentityResponse
$cfrom :: forall x.
GetCallerIdentityResponse -> Rep GetCallerIdentityResponse x
Prelude.Generic)
newGetCallerIdentityResponse ::
Prelude.Int ->
GetCallerIdentityResponse
newGetCallerIdentityResponse :: Int -> GetCallerIdentityResponse
newGetCallerIdentityResponse Int
pHttpStatus_ =
GetCallerIdentityResponse'
{ $sel:account:GetCallerIdentityResponse' :: Maybe Text
account =
forall a. Maybe a
Prelude.Nothing,
$sel:arn:GetCallerIdentityResponse' :: Maybe Text
arn = forall a. Maybe a
Prelude.Nothing,
$sel:userId:GetCallerIdentityResponse' :: Maybe Text
userId = forall a. Maybe a
Prelude.Nothing,
$sel:httpStatus:GetCallerIdentityResponse' :: Int
httpStatus = Int
pHttpStatus_
}
getCallerIdentityResponse_account :: Lens.Lens' GetCallerIdentityResponse (Prelude.Maybe Prelude.Text)
getCallerIdentityResponse_account :: Lens' GetCallerIdentityResponse (Maybe Text)
getCallerIdentityResponse_account = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetCallerIdentityResponse' {Maybe Text
account :: Maybe Text
$sel:account:GetCallerIdentityResponse' :: GetCallerIdentityResponse -> Maybe Text
account} -> Maybe Text
account) (\s :: GetCallerIdentityResponse
s@GetCallerIdentityResponse' {} Maybe Text
a -> GetCallerIdentityResponse
s {$sel:account:GetCallerIdentityResponse' :: Maybe Text
account = Maybe Text
a} :: GetCallerIdentityResponse)
getCallerIdentityResponse_arn :: Lens.Lens' GetCallerIdentityResponse (Prelude.Maybe Prelude.Text)
getCallerIdentityResponse_arn :: Lens' GetCallerIdentityResponse (Maybe Text)
getCallerIdentityResponse_arn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetCallerIdentityResponse' {Maybe Text
arn :: Maybe Text
$sel:arn:GetCallerIdentityResponse' :: GetCallerIdentityResponse -> Maybe Text
arn} -> Maybe Text
arn) (\s :: GetCallerIdentityResponse
s@GetCallerIdentityResponse' {} Maybe Text
a -> GetCallerIdentityResponse
s {$sel:arn:GetCallerIdentityResponse' :: Maybe Text
arn = Maybe Text
a} :: GetCallerIdentityResponse)
getCallerIdentityResponse_userId :: Lens.Lens' GetCallerIdentityResponse (Prelude.Maybe Prelude.Text)
getCallerIdentityResponse_userId :: Lens' GetCallerIdentityResponse (Maybe Text)
getCallerIdentityResponse_userId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetCallerIdentityResponse' {Maybe Text
userId :: Maybe Text
$sel:userId:GetCallerIdentityResponse' :: GetCallerIdentityResponse -> Maybe Text
userId} -> Maybe Text
userId) (\s :: GetCallerIdentityResponse
s@GetCallerIdentityResponse' {} Maybe Text
a -> GetCallerIdentityResponse
s {$sel:userId:GetCallerIdentityResponse' :: Maybe Text
userId = Maybe Text
a} :: GetCallerIdentityResponse)
getCallerIdentityResponse_httpStatus :: Lens.Lens' GetCallerIdentityResponse Prelude.Int
getCallerIdentityResponse_httpStatus :: Lens' GetCallerIdentityResponse Int
getCallerIdentityResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetCallerIdentityResponse' {Int
httpStatus :: Int
$sel:httpStatus:GetCallerIdentityResponse' :: GetCallerIdentityResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: GetCallerIdentityResponse
s@GetCallerIdentityResponse' {} Int
a -> GetCallerIdentityResponse
s {$sel:httpStatus:GetCallerIdentityResponse' :: Int
httpStatus = Int
a} :: GetCallerIdentityResponse)
instance Prelude.NFData GetCallerIdentityResponse where
rnf :: GetCallerIdentityResponse -> ()
rnf GetCallerIdentityResponse' {Int
Maybe Text
httpStatus :: Int
userId :: Maybe Text
arn :: Maybe Text
account :: Maybe Text
$sel:httpStatus:GetCallerIdentityResponse' :: GetCallerIdentityResponse -> Int
$sel:userId:GetCallerIdentityResponse' :: GetCallerIdentityResponse -> Maybe Text
$sel:arn:GetCallerIdentityResponse' :: GetCallerIdentityResponse -> Maybe Text
$sel:account:GetCallerIdentityResponse' :: GetCallerIdentityResponse -> Maybe Text
..} =
forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
account
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
arn
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
userId
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus