{-# 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.CognitoIdentityProvider.AdminGetDevice
-- 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 the device, as an administrator.
--
-- Calling this action requires developer credentials.
module Amazonka.CognitoIdentityProvider.AdminGetDevice
  ( -- * Creating a Request
    AdminGetDevice (..),
    newAdminGetDevice,

    -- * Request Lenses
    adminGetDevice_deviceKey,
    adminGetDevice_userPoolId,
    adminGetDevice_username,

    -- * Destructuring the Response
    AdminGetDeviceResponse (..),
    newAdminGetDeviceResponse,

    -- * Response Lenses
    adminGetDeviceResponse_httpStatus,
    adminGetDeviceResponse_device,
  )
where

import Amazonka.CognitoIdentityProvider.Types
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

-- | Represents the request to get the device, as an administrator.
--
-- /See:/ 'newAdminGetDevice' smart constructor.
data AdminGetDevice = AdminGetDevice'
  { -- | The device key.
    AdminGetDevice -> Text
deviceKey :: Prelude.Text,
    -- | The user pool ID.
    AdminGetDevice -> Text
userPoolId :: Prelude.Text,
    -- | The user name.
    AdminGetDevice -> Sensitive Text
username :: Data.Sensitive Prelude.Text
  }
  deriving (AdminGetDevice -> AdminGetDevice -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AdminGetDevice -> AdminGetDevice -> Bool
$c/= :: AdminGetDevice -> AdminGetDevice -> Bool
== :: AdminGetDevice -> AdminGetDevice -> Bool
$c== :: AdminGetDevice -> AdminGetDevice -> Bool
Prelude.Eq, Int -> AdminGetDevice -> ShowS
[AdminGetDevice] -> ShowS
AdminGetDevice -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AdminGetDevice] -> ShowS
$cshowList :: [AdminGetDevice] -> ShowS
show :: AdminGetDevice -> String
$cshow :: AdminGetDevice -> String
showsPrec :: Int -> AdminGetDevice -> ShowS
$cshowsPrec :: Int -> AdminGetDevice -> ShowS
Prelude.Show, forall x. Rep AdminGetDevice x -> AdminGetDevice
forall x. AdminGetDevice -> Rep AdminGetDevice x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AdminGetDevice x -> AdminGetDevice
$cfrom :: forall x. AdminGetDevice -> Rep AdminGetDevice x
Prelude.Generic)

-- |
-- Create a value of 'AdminGetDevice' 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:
--
-- 'deviceKey', 'adminGetDevice_deviceKey' - The device key.
--
-- 'userPoolId', 'adminGetDevice_userPoolId' - The user pool ID.
--
-- 'username', 'adminGetDevice_username' - The user name.
newAdminGetDevice ::
  -- | 'deviceKey'
  Prelude.Text ->
  -- | 'userPoolId'
  Prelude.Text ->
  -- | 'username'
  Prelude.Text ->
  AdminGetDevice
newAdminGetDevice :: Text -> Text -> Text -> AdminGetDevice
newAdminGetDevice Text
pDeviceKey_ Text
pUserPoolId_ Text
pUsername_ =
  AdminGetDevice'
    { $sel:deviceKey:AdminGetDevice' :: Text
deviceKey = Text
pDeviceKey_,
      $sel:userPoolId:AdminGetDevice' :: Text
userPoolId = Text
pUserPoolId_,
      $sel:username:AdminGetDevice' :: Sensitive Text
username = forall a. Iso' (Sensitive a) a
Data._Sensitive forall t b. AReview t b -> b -> t
Lens.# Text
pUsername_
    }

-- | The device key.
adminGetDevice_deviceKey :: Lens.Lens' AdminGetDevice Prelude.Text
adminGetDevice_deviceKey :: Lens' AdminGetDevice Text
adminGetDevice_deviceKey = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AdminGetDevice' {Text
deviceKey :: Text
$sel:deviceKey:AdminGetDevice' :: AdminGetDevice -> Text
deviceKey} -> Text
deviceKey) (\s :: AdminGetDevice
s@AdminGetDevice' {} Text
a -> AdminGetDevice
s {$sel:deviceKey:AdminGetDevice' :: Text
deviceKey = Text
a} :: AdminGetDevice)

-- | The user pool ID.
adminGetDevice_userPoolId :: Lens.Lens' AdminGetDevice Prelude.Text
adminGetDevice_userPoolId :: Lens' AdminGetDevice Text
adminGetDevice_userPoolId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AdminGetDevice' {Text
userPoolId :: Text
$sel:userPoolId:AdminGetDevice' :: AdminGetDevice -> Text
userPoolId} -> Text
userPoolId) (\s :: AdminGetDevice
s@AdminGetDevice' {} Text
a -> AdminGetDevice
s {$sel:userPoolId:AdminGetDevice' :: Text
userPoolId = Text
a} :: AdminGetDevice)

-- | The user name.
adminGetDevice_username :: Lens.Lens' AdminGetDevice Prelude.Text
adminGetDevice_username :: Lens' AdminGetDevice Text
adminGetDevice_username = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AdminGetDevice' {Sensitive Text
username :: Sensitive Text
$sel:username:AdminGetDevice' :: AdminGetDevice -> Sensitive Text
username} -> Sensitive Text
username) (\s :: AdminGetDevice
s@AdminGetDevice' {} Sensitive Text
a -> AdminGetDevice
s {$sel:username:AdminGetDevice' :: Sensitive Text
username = Sensitive Text
a} :: AdminGetDevice) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a. Iso' (Sensitive a) a
Data._Sensitive

instance Core.AWSRequest AdminGetDevice where
  type
    AWSResponse AdminGetDevice =
      AdminGetDeviceResponse
  request :: (Service -> Service) -> AdminGetDevice -> Request AdminGetDevice
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 AdminGetDevice
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse AdminGetDevice)))
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 ->
          Int -> DeviceType -> AdminGetDeviceResponse
AdminGetDeviceResponse'
            forall (f :: * -> *) a b. Functor 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))
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String a
Data..:> Key
"Device")
      )

instance Prelude.Hashable AdminGetDevice where
  hashWithSalt :: Int -> AdminGetDevice -> Int
hashWithSalt Int
_salt AdminGetDevice' {Text
Sensitive Text
username :: Sensitive Text
userPoolId :: Text
deviceKey :: Text
$sel:username:AdminGetDevice' :: AdminGetDevice -> Sensitive Text
$sel:userPoolId:AdminGetDevice' :: AdminGetDevice -> Text
$sel:deviceKey:AdminGetDevice' :: AdminGetDevice -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
deviceKey
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
userPoolId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Sensitive Text
username

instance Prelude.NFData AdminGetDevice where
  rnf :: AdminGetDevice -> ()
rnf AdminGetDevice' {Text
Sensitive Text
username :: Sensitive Text
userPoolId :: Text
deviceKey :: Text
$sel:username:AdminGetDevice' :: AdminGetDevice -> Sensitive Text
$sel:userPoolId:AdminGetDevice' :: AdminGetDevice -> Text
$sel:deviceKey:AdminGetDevice' :: AdminGetDevice -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
deviceKey
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
userPoolId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Sensitive Text
username

instance Data.ToHeaders AdminGetDevice where
  toHeaders :: AdminGetDevice -> 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
"AWSCognitoIdentityProviderService.AdminGetDevice" ::
                          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 AdminGetDevice where
  toJSON :: AdminGetDevice -> Value
toJSON AdminGetDevice' {Text
Sensitive Text
username :: Sensitive Text
userPoolId :: Text
deviceKey :: Text
$sel:username:AdminGetDevice' :: AdminGetDevice -> Sensitive Text
$sel:userPoolId:AdminGetDevice' :: AdminGetDevice -> Text
$sel:deviceKey:AdminGetDevice' :: AdminGetDevice -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ forall a. a -> Maybe a
Prelude.Just (Key
"DeviceKey" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
deviceKey),
            forall a. a -> Maybe a
Prelude.Just (Key
"UserPoolId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
userPoolId),
            forall a. a -> Maybe a
Prelude.Just (Key
"Username" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Sensitive Text
username)
          ]
      )

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

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

-- | Gets the device response, as an administrator.
--
-- /See:/ 'newAdminGetDeviceResponse' smart constructor.
data AdminGetDeviceResponse = AdminGetDeviceResponse'
  { -- | The response's http status code.
    AdminGetDeviceResponse -> Int
httpStatus :: Prelude.Int,
    -- | The device.
    AdminGetDeviceResponse -> DeviceType
device :: DeviceType
  }
  deriving (AdminGetDeviceResponse -> AdminGetDeviceResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AdminGetDeviceResponse -> AdminGetDeviceResponse -> Bool
$c/= :: AdminGetDeviceResponse -> AdminGetDeviceResponse -> Bool
== :: AdminGetDeviceResponse -> AdminGetDeviceResponse -> Bool
$c== :: AdminGetDeviceResponse -> AdminGetDeviceResponse -> Bool
Prelude.Eq, Int -> AdminGetDeviceResponse -> ShowS
[AdminGetDeviceResponse] -> ShowS
AdminGetDeviceResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AdminGetDeviceResponse] -> ShowS
$cshowList :: [AdminGetDeviceResponse] -> ShowS
show :: AdminGetDeviceResponse -> String
$cshow :: AdminGetDeviceResponse -> String
showsPrec :: Int -> AdminGetDeviceResponse -> ShowS
$cshowsPrec :: Int -> AdminGetDeviceResponse -> ShowS
Prelude.Show, forall x. Rep AdminGetDeviceResponse x -> AdminGetDeviceResponse
forall x. AdminGetDeviceResponse -> Rep AdminGetDeviceResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AdminGetDeviceResponse x -> AdminGetDeviceResponse
$cfrom :: forall x. AdminGetDeviceResponse -> Rep AdminGetDeviceResponse x
Prelude.Generic)

-- |
-- Create a value of 'AdminGetDeviceResponse' 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:
--
-- 'httpStatus', 'adminGetDeviceResponse_httpStatus' - The response's http status code.
--
-- 'device', 'adminGetDeviceResponse_device' - The device.
newAdminGetDeviceResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'device'
  DeviceType ->
  AdminGetDeviceResponse
newAdminGetDeviceResponse :: Int -> DeviceType -> AdminGetDeviceResponse
newAdminGetDeviceResponse Int
pHttpStatus_ DeviceType
pDevice_ =
  AdminGetDeviceResponse'
    { $sel:httpStatus:AdminGetDeviceResponse' :: Int
httpStatus = Int
pHttpStatus_,
      $sel:device:AdminGetDeviceResponse' :: DeviceType
device = DeviceType
pDevice_
    }

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

-- | The device.
adminGetDeviceResponse_device :: Lens.Lens' AdminGetDeviceResponse DeviceType
adminGetDeviceResponse_device :: Lens' AdminGetDeviceResponse DeviceType
adminGetDeviceResponse_device = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AdminGetDeviceResponse' {DeviceType
device :: DeviceType
$sel:device:AdminGetDeviceResponse' :: AdminGetDeviceResponse -> DeviceType
device} -> DeviceType
device) (\s :: AdminGetDeviceResponse
s@AdminGetDeviceResponse' {} DeviceType
a -> AdminGetDeviceResponse
s {$sel:device:AdminGetDeviceResponse' :: DeviceType
device = DeviceType
a} :: AdminGetDeviceResponse)

instance Prelude.NFData AdminGetDeviceResponse where
  rnf :: AdminGetDeviceResponse -> ()
rnf AdminGetDeviceResponse' {Int
DeviceType
device :: DeviceType
httpStatus :: Int
$sel:device:AdminGetDeviceResponse' :: AdminGetDeviceResponse -> DeviceType
$sel:httpStatus:AdminGetDeviceResponse' :: AdminGetDeviceResponse -> Int
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf DeviceType
device