{-# 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.IoT.TestAuthorization
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Tests if a specified principal is authorized to perform an IoT action on
-- a specified resource. Use this to test and debug the authorization
-- behavior of devices that connect to the IoT device gateway.
--
-- Requires permission to access the
-- <https://docs.aws.amazon.com/service-authorization/latest/reference/list_awsiot.html#awsiot-actions-as-permissions TestAuthorization>
-- action.
module Amazonka.IoT.TestAuthorization
  ( -- * Creating a Request
    TestAuthorization (..),
    newTestAuthorization,

    -- * Request Lenses
    testAuthorization_clientId,
    testAuthorization_cognitoIdentityPoolId,
    testAuthorization_policyNamesToAdd,
    testAuthorization_policyNamesToSkip,
    testAuthorization_principal,
    testAuthorization_authInfos,

    -- * Destructuring the Response
    TestAuthorizationResponse (..),
    newTestAuthorizationResponse,

    -- * Response Lenses
    testAuthorizationResponse_authResults,
    testAuthorizationResponse_httpStatus,
  )
where

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

-- | /See:/ 'newTestAuthorization' smart constructor.
data TestAuthorization = TestAuthorization'
  { -- | The MQTT client ID.
    TestAuthorization -> Maybe Text
clientId :: Prelude.Maybe Prelude.Text,
    -- | The Cognito identity pool ID.
    TestAuthorization -> Maybe Text
cognitoIdentityPoolId :: Prelude.Maybe Prelude.Text,
    -- | When testing custom authorization, the policies specified here are
    -- treated as if they are attached to the principal being authorized.
    TestAuthorization -> Maybe [Text]
policyNamesToAdd :: Prelude.Maybe [Prelude.Text],
    -- | When testing custom authorization, the policies specified here are
    -- treated as if they are not attached to the principal being authorized.
    TestAuthorization -> Maybe [Text]
policyNamesToSkip :: Prelude.Maybe [Prelude.Text],
    -- | The principal. Valid principals are CertificateArn
    -- (arn:aws:iot:/region/:/accountId/:cert\//certificateId/), thingGroupArn
    -- (arn:aws:iot:/region/:/accountId/:thinggroup\//groupName/) and CognitoId
    -- (/region/:/id/).
    TestAuthorization -> Maybe Text
principal :: Prelude.Maybe Prelude.Text,
    -- | A list of authorization info objects. Simulating authorization will
    -- create a response for each @authInfo@ object in the list.
    TestAuthorization -> NonEmpty AuthInfo
authInfos :: Prelude.NonEmpty AuthInfo
  }
  deriving (TestAuthorization -> TestAuthorization -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TestAuthorization -> TestAuthorization -> Bool
$c/= :: TestAuthorization -> TestAuthorization -> Bool
== :: TestAuthorization -> TestAuthorization -> Bool
$c== :: TestAuthorization -> TestAuthorization -> Bool
Prelude.Eq, ReadPrec [TestAuthorization]
ReadPrec TestAuthorization
Int -> ReadS TestAuthorization
ReadS [TestAuthorization]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [TestAuthorization]
$creadListPrec :: ReadPrec [TestAuthorization]
readPrec :: ReadPrec TestAuthorization
$creadPrec :: ReadPrec TestAuthorization
readList :: ReadS [TestAuthorization]
$creadList :: ReadS [TestAuthorization]
readsPrec :: Int -> ReadS TestAuthorization
$creadsPrec :: Int -> ReadS TestAuthorization
Prelude.Read, Int -> TestAuthorization -> ShowS
[TestAuthorization] -> ShowS
TestAuthorization -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TestAuthorization] -> ShowS
$cshowList :: [TestAuthorization] -> ShowS
show :: TestAuthorization -> String
$cshow :: TestAuthorization -> String
showsPrec :: Int -> TestAuthorization -> ShowS
$cshowsPrec :: Int -> TestAuthorization -> ShowS
Prelude.Show, forall x. Rep TestAuthorization x -> TestAuthorization
forall x. TestAuthorization -> Rep TestAuthorization x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TestAuthorization x -> TestAuthorization
$cfrom :: forall x. TestAuthorization -> Rep TestAuthorization x
Prelude.Generic)

-- |
-- Create a value of 'TestAuthorization' 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:
--
-- 'clientId', 'testAuthorization_clientId' - The MQTT client ID.
--
-- 'cognitoIdentityPoolId', 'testAuthorization_cognitoIdentityPoolId' - The Cognito identity pool ID.
--
-- 'policyNamesToAdd', 'testAuthorization_policyNamesToAdd' - When testing custom authorization, the policies specified here are
-- treated as if they are attached to the principal being authorized.
--
-- 'policyNamesToSkip', 'testAuthorization_policyNamesToSkip' - When testing custom authorization, the policies specified here are
-- treated as if they are not attached to the principal being authorized.
--
-- 'principal', 'testAuthorization_principal' - The principal. Valid principals are CertificateArn
-- (arn:aws:iot:/region/:/accountId/:cert\//certificateId/), thingGroupArn
-- (arn:aws:iot:/region/:/accountId/:thinggroup\//groupName/) and CognitoId
-- (/region/:/id/).
--
-- 'authInfos', 'testAuthorization_authInfos' - A list of authorization info objects. Simulating authorization will
-- create a response for each @authInfo@ object in the list.
newTestAuthorization ::
  -- | 'authInfos'
  Prelude.NonEmpty AuthInfo ->
  TestAuthorization
newTestAuthorization :: NonEmpty AuthInfo -> TestAuthorization
newTestAuthorization NonEmpty AuthInfo
pAuthInfos_ =
  TestAuthorization'
    { $sel:clientId:TestAuthorization' :: Maybe Text
clientId = forall a. Maybe a
Prelude.Nothing,
      $sel:cognitoIdentityPoolId:TestAuthorization' :: Maybe Text
cognitoIdentityPoolId = forall a. Maybe a
Prelude.Nothing,
      $sel:policyNamesToAdd:TestAuthorization' :: Maybe [Text]
policyNamesToAdd = forall a. Maybe a
Prelude.Nothing,
      $sel:policyNamesToSkip:TestAuthorization' :: Maybe [Text]
policyNamesToSkip = forall a. Maybe a
Prelude.Nothing,
      $sel:principal:TestAuthorization' :: Maybe Text
principal = forall a. Maybe a
Prelude.Nothing,
      $sel:authInfos:TestAuthorization' :: NonEmpty AuthInfo
authInfos = forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced forall t b. AReview t b -> b -> t
Lens.# NonEmpty AuthInfo
pAuthInfos_
    }

-- | The MQTT client ID.
testAuthorization_clientId :: Lens.Lens' TestAuthorization (Prelude.Maybe Prelude.Text)
testAuthorization_clientId :: Lens' TestAuthorization (Maybe Text)
testAuthorization_clientId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TestAuthorization' {Maybe Text
clientId :: Maybe Text
$sel:clientId:TestAuthorization' :: TestAuthorization -> Maybe Text
clientId} -> Maybe Text
clientId) (\s :: TestAuthorization
s@TestAuthorization' {} Maybe Text
a -> TestAuthorization
s {$sel:clientId:TestAuthorization' :: Maybe Text
clientId = Maybe Text
a} :: TestAuthorization)

-- | The Cognito identity pool ID.
testAuthorization_cognitoIdentityPoolId :: Lens.Lens' TestAuthorization (Prelude.Maybe Prelude.Text)
testAuthorization_cognitoIdentityPoolId :: Lens' TestAuthorization (Maybe Text)
testAuthorization_cognitoIdentityPoolId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TestAuthorization' {Maybe Text
cognitoIdentityPoolId :: Maybe Text
$sel:cognitoIdentityPoolId:TestAuthorization' :: TestAuthorization -> Maybe Text
cognitoIdentityPoolId} -> Maybe Text
cognitoIdentityPoolId) (\s :: TestAuthorization
s@TestAuthorization' {} Maybe Text
a -> TestAuthorization
s {$sel:cognitoIdentityPoolId:TestAuthorization' :: Maybe Text
cognitoIdentityPoolId = Maybe Text
a} :: TestAuthorization)

-- | When testing custom authorization, the policies specified here are
-- treated as if they are attached to the principal being authorized.
testAuthorization_policyNamesToAdd :: Lens.Lens' TestAuthorization (Prelude.Maybe [Prelude.Text])
testAuthorization_policyNamesToAdd :: Lens' TestAuthorization (Maybe [Text])
testAuthorization_policyNamesToAdd = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TestAuthorization' {Maybe [Text]
policyNamesToAdd :: Maybe [Text]
$sel:policyNamesToAdd:TestAuthorization' :: TestAuthorization -> Maybe [Text]
policyNamesToAdd} -> Maybe [Text]
policyNamesToAdd) (\s :: TestAuthorization
s@TestAuthorization' {} Maybe [Text]
a -> TestAuthorization
s {$sel:policyNamesToAdd:TestAuthorization' :: Maybe [Text]
policyNamesToAdd = Maybe [Text]
a} :: TestAuthorization) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | When testing custom authorization, the policies specified here are
-- treated as if they are not attached to the principal being authorized.
testAuthorization_policyNamesToSkip :: Lens.Lens' TestAuthorization (Prelude.Maybe [Prelude.Text])
testAuthorization_policyNamesToSkip :: Lens' TestAuthorization (Maybe [Text])
testAuthorization_policyNamesToSkip = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TestAuthorization' {Maybe [Text]
policyNamesToSkip :: Maybe [Text]
$sel:policyNamesToSkip:TestAuthorization' :: TestAuthorization -> Maybe [Text]
policyNamesToSkip} -> Maybe [Text]
policyNamesToSkip) (\s :: TestAuthorization
s@TestAuthorization' {} Maybe [Text]
a -> TestAuthorization
s {$sel:policyNamesToSkip:TestAuthorization' :: Maybe [Text]
policyNamesToSkip = Maybe [Text]
a} :: TestAuthorization) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | The principal. Valid principals are CertificateArn
-- (arn:aws:iot:/region/:/accountId/:cert\//certificateId/), thingGroupArn
-- (arn:aws:iot:/region/:/accountId/:thinggroup\//groupName/) and CognitoId
-- (/region/:/id/).
testAuthorization_principal :: Lens.Lens' TestAuthorization (Prelude.Maybe Prelude.Text)
testAuthorization_principal :: Lens' TestAuthorization (Maybe Text)
testAuthorization_principal = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TestAuthorization' {Maybe Text
principal :: Maybe Text
$sel:principal:TestAuthorization' :: TestAuthorization -> Maybe Text
principal} -> Maybe Text
principal) (\s :: TestAuthorization
s@TestAuthorization' {} Maybe Text
a -> TestAuthorization
s {$sel:principal:TestAuthorization' :: Maybe Text
principal = Maybe Text
a} :: TestAuthorization)

-- | A list of authorization info objects. Simulating authorization will
-- create a response for each @authInfo@ object in the list.
testAuthorization_authInfos :: Lens.Lens' TestAuthorization (Prelude.NonEmpty AuthInfo)
testAuthorization_authInfos :: Lens' TestAuthorization (NonEmpty AuthInfo)
testAuthorization_authInfos = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TestAuthorization' {NonEmpty AuthInfo
authInfos :: NonEmpty AuthInfo
$sel:authInfos:TestAuthorization' :: TestAuthorization -> NonEmpty AuthInfo
authInfos} -> NonEmpty AuthInfo
authInfos) (\s :: TestAuthorization
s@TestAuthorization' {} NonEmpty AuthInfo
a -> TestAuthorization
s {$sel:authInfos:TestAuthorization' :: NonEmpty AuthInfo
authInfos = NonEmpty AuthInfo
a} :: TestAuthorization) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

instance Core.AWSRequest TestAuthorization where
  type
    AWSResponse TestAuthorization =
      TestAuthorizationResponse
  request :: (Service -> Service)
-> TestAuthorization -> Request TestAuthorization
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 TestAuthorization
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse TestAuthorization)))
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 [AuthResult] -> Int -> TestAuthorizationResponse
TestAuthorizationResponse'
            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
"authResults" forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty)
            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 TestAuthorization where
  hashWithSalt :: Int -> TestAuthorization -> Int
hashWithSalt Int
_salt TestAuthorization' {Maybe [Text]
Maybe Text
NonEmpty AuthInfo
authInfos :: NonEmpty AuthInfo
principal :: Maybe Text
policyNamesToSkip :: Maybe [Text]
policyNamesToAdd :: Maybe [Text]
cognitoIdentityPoolId :: Maybe Text
clientId :: Maybe Text
$sel:authInfos:TestAuthorization' :: TestAuthorization -> NonEmpty AuthInfo
$sel:principal:TestAuthorization' :: TestAuthorization -> Maybe Text
$sel:policyNamesToSkip:TestAuthorization' :: TestAuthorization -> Maybe [Text]
$sel:policyNamesToAdd:TestAuthorization' :: TestAuthorization -> Maybe [Text]
$sel:cognitoIdentityPoolId:TestAuthorization' :: TestAuthorization -> Maybe Text
$sel:clientId:TestAuthorization' :: TestAuthorization -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
clientId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
cognitoIdentityPoolId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
policyNamesToAdd
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
policyNamesToSkip
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
principal
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` NonEmpty AuthInfo
authInfos

instance Prelude.NFData TestAuthorization where
  rnf :: TestAuthorization -> ()
rnf TestAuthorization' {Maybe [Text]
Maybe Text
NonEmpty AuthInfo
authInfos :: NonEmpty AuthInfo
principal :: Maybe Text
policyNamesToSkip :: Maybe [Text]
policyNamesToAdd :: Maybe [Text]
cognitoIdentityPoolId :: Maybe Text
clientId :: Maybe Text
$sel:authInfos:TestAuthorization' :: TestAuthorization -> NonEmpty AuthInfo
$sel:principal:TestAuthorization' :: TestAuthorization -> Maybe Text
$sel:policyNamesToSkip:TestAuthorization' :: TestAuthorization -> Maybe [Text]
$sel:policyNamesToAdd:TestAuthorization' :: TestAuthorization -> Maybe [Text]
$sel:cognitoIdentityPoolId:TestAuthorization' :: TestAuthorization -> Maybe Text
$sel:clientId:TestAuthorization' :: TestAuthorization -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
clientId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
cognitoIdentityPoolId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
policyNamesToAdd
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
policyNamesToSkip
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
principal
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf NonEmpty AuthInfo
authInfos

instance Data.ToHeaders TestAuthorization where
  toHeaders :: TestAuthorization -> ResponseHeaders
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

instance Data.ToJSON TestAuthorization where
  toJSON :: TestAuthorization -> Value
toJSON TestAuthorization' {Maybe [Text]
Maybe Text
NonEmpty AuthInfo
authInfos :: NonEmpty AuthInfo
principal :: Maybe Text
policyNamesToSkip :: Maybe [Text]
policyNamesToAdd :: Maybe [Text]
cognitoIdentityPoolId :: Maybe Text
clientId :: Maybe Text
$sel:authInfos:TestAuthorization' :: TestAuthorization -> NonEmpty AuthInfo
$sel:principal:TestAuthorization' :: TestAuthorization -> Maybe Text
$sel:policyNamesToSkip:TestAuthorization' :: TestAuthorization -> Maybe [Text]
$sel:policyNamesToAdd:TestAuthorization' :: TestAuthorization -> Maybe [Text]
$sel:cognitoIdentityPoolId:TestAuthorization' :: TestAuthorization -> Maybe Text
$sel:clientId:TestAuthorization' :: TestAuthorization -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"cognitoIdentityPoolId" 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
cognitoIdentityPoolId,
            (Key
"policyNamesToAdd" 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]
policyNamesToAdd,
            (Key
"policyNamesToSkip" 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]
policyNamesToSkip,
            (Key
"principal" 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
principal,
            forall a. a -> Maybe a
Prelude.Just (Key
"authInfos" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= NonEmpty AuthInfo
authInfos)
          ]
      )

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

instance Data.ToQuery TestAuthorization where
  toQuery :: TestAuthorization -> QueryString
toQuery TestAuthorization' {Maybe [Text]
Maybe Text
NonEmpty AuthInfo
authInfos :: NonEmpty AuthInfo
principal :: Maybe Text
policyNamesToSkip :: Maybe [Text]
policyNamesToAdd :: Maybe [Text]
cognitoIdentityPoolId :: Maybe Text
clientId :: Maybe Text
$sel:authInfos:TestAuthorization' :: TestAuthorization -> NonEmpty AuthInfo
$sel:principal:TestAuthorization' :: TestAuthorization -> Maybe Text
$sel:policyNamesToSkip:TestAuthorization' :: TestAuthorization -> Maybe [Text]
$sel:policyNamesToAdd:TestAuthorization' :: TestAuthorization -> Maybe [Text]
$sel:cognitoIdentityPoolId:TestAuthorization' :: TestAuthorization -> Maybe Text
$sel:clientId:TestAuthorization' :: TestAuthorization -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat [ByteString
"clientId" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
clientId]

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

-- |
-- Create a value of 'TestAuthorizationResponse' 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:
--
-- 'authResults', 'testAuthorizationResponse_authResults' - The authentication results.
--
-- 'httpStatus', 'testAuthorizationResponse_httpStatus' - The response's http status code.
newTestAuthorizationResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  TestAuthorizationResponse
newTestAuthorizationResponse :: Int -> TestAuthorizationResponse
newTestAuthorizationResponse Int
pHttpStatus_ =
  TestAuthorizationResponse'
    { $sel:authResults:TestAuthorizationResponse' :: Maybe [AuthResult]
authResults =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:TestAuthorizationResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The authentication results.
testAuthorizationResponse_authResults :: Lens.Lens' TestAuthorizationResponse (Prelude.Maybe [AuthResult])
testAuthorizationResponse_authResults :: Lens' TestAuthorizationResponse (Maybe [AuthResult])
testAuthorizationResponse_authResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TestAuthorizationResponse' {Maybe [AuthResult]
authResults :: Maybe [AuthResult]
$sel:authResults:TestAuthorizationResponse' :: TestAuthorizationResponse -> Maybe [AuthResult]
authResults} -> Maybe [AuthResult]
authResults) (\s :: TestAuthorizationResponse
s@TestAuthorizationResponse' {} Maybe [AuthResult]
a -> TestAuthorizationResponse
s {$sel:authResults:TestAuthorizationResponse' :: Maybe [AuthResult]
authResults = Maybe [AuthResult]
a} :: TestAuthorizationResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

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

instance Prelude.NFData TestAuthorizationResponse where
  rnf :: TestAuthorizationResponse -> ()
rnf TestAuthorizationResponse' {Int
Maybe [AuthResult]
httpStatus :: Int
authResults :: Maybe [AuthResult]
$sel:httpStatus:TestAuthorizationResponse' :: TestAuthorizationResponse -> Int
$sel:authResults:TestAuthorizationResponse' :: TestAuthorizationResponse -> Maybe [AuthResult]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [AuthResult]
authResults
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus