{-# 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.Grafana.DescribeWorkspaceAuthentication
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Displays information about the authentication methods used in one Amazon
-- Managed Grafana workspace.
module Amazonka.Grafana.DescribeWorkspaceAuthentication
  ( -- * Creating a Request
    DescribeWorkspaceAuthentication (..),
    newDescribeWorkspaceAuthentication,

    -- * Request Lenses
    describeWorkspaceAuthentication_workspaceId,

    -- * Destructuring the Response
    DescribeWorkspaceAuthenticationResponse (..),
    newDescribeWorkspaceAuthenticationResponse,

    -- * Response Lenses
    describeWorkspaceAuthenticationResponse_httpStatus,
    describeWorkspaceAuthenticationResponse_authentication,
  )
where

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

-- | /See:/ 'newDescribeWorkspaceAuthentication' smart constructor.
data DescribeWorkspaceAuthentication = DescribeWorkspaceAuthentication'
  { -- | The ID of the workspace to return authentication information about.
    DescribeWorkspaceAuthentication -> Text
workspaceId :: Prelude.Text
  }
  deriving (DescribeWorkspaceAuthentication
-> DescribeWorkspaceAuthentication -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeWorkspaceAuthentication
-> DescribeWorkspaceAuthentication -> Bool
$c/= :: DescribeWorkspaceAuthentication
-> DescribeWorkspaceAuthentication -> Bool
== :: DescribeWorkspaceAuthentication
-> DescribeWorkspaceAuthentication -> Bool
$c== :: DescribeWorkspaceAuthentication
-> DescribeWorkspaceAuthentication -> Bool
Prelude.Eq, ReadPrec [DescribeWorkspaceAuthentication]
ReadPrec DescribeWorkspaceAuthentication
Int -> ReadS DescribeWorkspaceAuthentication
ReadS [DescribeWorkspaceAuthentication]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeWorkspaceAuthentication]
$creadListPrec :: ReadPrec [DescribeWorkspaceAuthentication]
readPrec :: ReadPrec DescribeWorkspaceAuthentication
$creadPrec :: ReadPrec DescribeWorkspaceAuthentication
readList :: ReadS [DescribeWorkspaceAuthentication]
$creadList :: ReadS [DescribeWorkspaceAuthentication]
readsPrec :: Int -> ReadS DescribeWorkspaceAuthentication
$creadsPrec :: Int -> ReadS DescribeWorkspaceAuthentication
Prelude.Read, Int -> DescribeWorkspaceAuthentication -> ShowS
[DescribeWorkspaceAuthentication] -> ShowS
DescribeWorkspaceAuthentication -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeWorkspaceAuthentication] -> ShowS
$cshowList :: [DescribeWorkspaceAuthentication] -> ShowS
show :: DescribeWorkspaceAuthentication -> String
$cshow :: DescribeWorkspaceAuthentication -> String
showsPrec :: Int -> DescribeWorkspaceAuthentication -> ShowS
$cshowsPrec :: Int -> DescribeWorkspaceAuthentication -> ShowS
Prelude.Show, forall x.
Rep DescribeWorkspaceAuthentication x
-> DescribeWorkspaceAuthentication
forall x.
DescribeWorkspaceAuthentication
-> Rep DescribeWorkspaceAuthentication x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeWorkspaceAuthentication x
-> DescribeWorkspaceAuthentication
$cfrom :: forall x.
DescribeWorkspaceAuthentication
-> Rep DescribeWorkspaceAuthentication x
Prelude.Generic)

-- |
-- Create a value of 'DescribeWorkspaceAuthentication' 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:
--
-- 'workspaceId', 'describeWorkspaceAuthentication_workspaceId' - The ID of the workspace to return authentication information about.
newDescribeWorkspaceAuthentication ::
  -- | 'workspaceId'
  Prelude.Text ->
  DescribeWorkspaceAuthentication
newDescribeWorkspaceAuthentication :: Text -> DescribeWorkspaceAuthentication
newDescribeWorkspaceAuthentication Text
pWorkspaceId_ =
  DescribeWorkspaceAuthentication'
    { $sel:workspaceId:DescribeWorkspaceAuthentication' :: Text
workspaceId =
        Text
pWorkspaceId_
    }

-- | The ID of the workspace to return authentication information about.
describeWorkspaceAuthentication_workspaceId :: Lens.Lens' DescribeWorkspaceAuthentication Prelude.Text
describeWorkspaceAuthentication_workspaceId :: Lens' DescribeWorkspaceAuthentication Text
describeWorkspaceAuthentication_workspaceId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeWorkspaceAuthentication' {Text
workspaceId :: Text
$sel:workspaceId:DescribeWorkspaceAuthentication' :: DescribeWorkspaceAuthentication -> Text
workspaceId} -> Text
workspaceId) (\s :: DescribeWorkspaceAuthentication
s@DescribeWorkspaceAuthentication' {} Text
a -> DescribeWorkspaceAuthentication
s {$sel:workspaceId:DescribeWorkspaceAuthentication' :: Text
workspaceId = Text
a} :: DescribeWorkspaceAuthentication)

instance
  Core.AWSRequest
    DescribeWorkspaceAuthentication
  where
  type
    AWSResponse DescribeWorkspaceAuthentication =
      DescribeWorkspaceAuthenticationResponse
  request :: (Service -> Service)
-> DescribeWorkspaceAuthentication
-> Request DescribeWorkspaceAuthentication
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 DescribeWorkspaceAuthentication
-> ClientResponse ClientBody
-> m (Either
        Error
        (ClientResponse (AWSResponse DescribeWorkspaceAuthentication)))
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
-> AuthenticationDescription
-> DescribeWorkspaceAuthenticationResponse
DescribeWorkspaceAuthenticationResponse'
            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
"authentication")
      )

instance
  Prelude.Hashable
    DescribeWorkspaceAuthentication
  where
  hashWithSalt :: Int -> DescribeWorkspaceAuthentication -> Int
hashWithSalt
    Int
_salt
    DescribeWorkspaceAuthentication' {Text
workspaceId :: Text
$sel:workspaceId:DescribeWorkspaceAuthentication' :: DescribeWorkspaceAuthentication -> Text
..} =
      Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
workspaceId

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

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

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

-- | /See:/ 'newDescribeWorkspaceAuthenticationResponse' smart constructor.
data DescribeWorkspaceAuthenticationResponse = DescribeWorkspaceAuthenticationResponse'
  { -- | The response's http status code.
    DescribeWorkspaceAuthenticationResponse -> Int
httpStatus :: Prelude.Int,
    -- | A structure containing information about the authentication methods used
    -- in the workspace.
    DescribeWorkspaceAuthenticationResponse
-> AuthenticationDescription
authentication :: AuthenticationDescription
  }
  deriving (DescribeWorkspaceAuthenticationResponse
-> DescribeWorkspaceAuthenticationResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeWorkspaceAuthenticationResponse
-> DescribeWorkspaceAuthenticationResponse -> Bool
$c/= :: DescribeWorkspaceAuthenticationResponse
-> DescribeWorkspaceAuthenticationResponse -> Bool
== :: DescribeWorkspaceAuthenticationResponse
-> DescribeWorkspaceAuthenticationResponse -> Bool
$c== :: DescribeWorkspaceAuthenticationResponse
-> DescribeWorkspaceAuthenticationResponse -> Bool
Prelude.Eq, ReadPrec [DescribeWorkspaceAuthenticationResponse]
ReadPrec DescribeWorkspaceAuthenticationResponse
Int -> ReadS DescribeWorkspaceAuthenticationResponse
ReadS [DescribeWorkspaceAuthenticationResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeWorkspaceAuthenticationResponse]
$creadListPrec :: ReadPrec [DescribeWorkspaceAuthenticationResponse]
readPrec :: ReadPrec DescribeWorkspaceAuthenticationResponse
$creadPrec :: ReadPrec DescribeWorkspaceAuthenticationResponse
readList :: ReadS [DescribeWorkspaceAuthenticationResponse]
$creadList :: ReadS [DescribeWorkspaceAuthenticationResponse]
readsPrec :: Int -> ReadS DescribeWorkspaceAuthenticationResponse
$creadsPrec :: Int -> ReadS DescribeWorkspaceAuthenticationResponse
Prelude.Read, Int -> DescribeWorkspaceAuthenticationResponse -> ShowS
[DescribeWorkspaceAuthenticationResponse] -> ShowS
DescribeWorkspaceAuthenticationResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeWorkspaceAuthenticationResponse] -> ShowS
$cshowList :: [DescribeWorkspaceAuthenticationResponse] -> ShowS
show :: DescribeWorkspaceAuthenticationResponse -> String
$cshow :: DescribeWorkspaceAuthenticationResponse -> String
showsPrec :: Int -> DescribeWorkspaceAuthenticationResponse -> ShowS
$cshowsPrec :: Int -> DescribeWorkspaceAuthenticationResponse -> ShowS
Prelude.Show, forall x.
Rep DescribeWorkspaceAuthenticationResponse x
-> DescribeWorkspaceAuthenticationResponse
forall x.
DescribeWorkspaceAuthenticationResponse
-> Rep DescribeWorkspaceAuthenticationResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeWorkspaceAuthenticationResponse x
-> DescribeWorkspaceAuthenticationResponse
$cfrom :: forall x.
DescribeWorkspaceAuthenticationResponse
-> Rep DescribeWorkspaceAuthenticationResponse x
Prelude.Generic)

-- |
-- Create a value of 'DescribeWorkspaceAuthenticationResponse' 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', 'describeWorkspaceAuthenticationResponse_httpStatus' - The response's http status code.
--
-- 'authentication', 'describeWorkspaceAuthenticationResponse_authentication' - A structure containing information about the authentication methods used
-- in the workspace.
newDescribeWorkspaceAuthenticationResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'authentication'
  AuthenticationDescription ->
  DescribeWorkspaceAuthenticationResponse
newDescribeWorkspaceAuthenticationResponse :: Int
-> AuthenticationDescription
-> DescribeWorkspaceAuthenticationResponse
newDescribeWorkspaceAuthenticationResponse
  Int
pHttpStatus_
  AuthenticationDescription
pAuthentication_ =
    DescribeWorkspaceAuthenticationResponse'
      { $sel:httpStatus:DescribeWorkspaceAuthenticationResponse' :: Int
httpStatus =
          Int
pHttpStatus_,
        $sel:authentication:DescribeWorkspaceAuthenticationResponse' :: AuthenticationDescription
authentication = AuthenticationDescription
pAuthentication_
      }

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

-- | A structure containing information about the authentication methods used
-- in the workspace.
describeWorkspaceAuthenticationResponse_authentication :: Lens.Lens' DescribeWorkspaceAuthenticationResponse AuthenticationDescription
describeWorkspaceAuthenticationResponse_authentication :: Lens'
  DescribeWorkspaceAuthenticationResponse AuthenticationDescription
describeWorkspaceAuthenticationResponse_authentication = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeWorkspaceAuthenticationResponse' {AuthenticationDescription
authentication :: AuthenticationDescription
$sel:authentication:DescribeWorkspaceAuthenticationResponse' :: DescribeWorkspaceAuthenticationResponse
-> AuthenticationDescription
authentication} -> AuthenticationDescription
authentication) (\s :: DescribeWorkspaceAuthenticationResponse
s@DescribeWorkspaceAuthenticationResponse' {} AuthenticationDescription
a -> DescribeWorkspaceAuthenticationResponse
s {$sel:authentication:DescribeWorkspaceAuthenticationResponse' :: AuthenticationDescription
authentication = AuthenticationDescription
a} :: DescribeWorkspaceAuthenticationResponse)

instance
  Prelude.NFData
    DescribeWorkspaceAuthenticationResponse
  where
  rnf :: DescribeWorkspaceAuthenticationResponse -> ()
rnf DescribeWorkspaceAuthenticationResponse' {Int
AuthenticationDescription
authentication :: AuthenticationDescription
httpStatus :: Int
$sel:authentication:DescribeWorkspaceAuthenticationResponse' :: DescribeWorkspaceAuthenticationResponse
-> AuthenticationDescription
$sel:httpStatus:DescribeWorkspaceAuthenticationResponse' :: DescribeWorkspaceAuthenticationResponse -> 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 AuthenticationDescription
authentication