{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
{-# OPTIONS_GHC -fno-warn-unused-matches #-}

-- Derived from AWS service descriptions, licensed under Apache 2.0.

-- |
-- Module      : Amazonka.EC2.Types.OidcOptions
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
module Amazonka.EC2.Types.OidcOptions where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.EC2.Internal
import qualified Amazonka.Prelude as Prelude

-- | Options for OIDC-based, user-identity type trust provider.
--
-- /See:/ 'newOidcOptions' smart constructor.
data OidcOptions = OidcOptions'
  { -- | The OIDC authorization endpoint.
    OidcOptions -> Maybe Text
authorizationEndpoint :: Prelude.Maybe Prelude.Text,
    -- | The client identifier.
    OidcOptions -> Maybe Text
clientId :: Prelude.Maybe Prelude.Text,
    -- | The client secret.
    OidcOptions -> Maybe Text
clientSecret :: Prelude.Maybe Prelude.Text,
    -- | The OIDC issuer.
    OidcOptions -> Maybe Text
issuer :: Prelude.Maybe Prelude.Text,
    -- | The OpenID Connect (OIDC) scope specified.
    OidcOptions -> Maybe Text
scope :: Prelude.Maybe Prelude.Text,
    -- | The OIDC token endpoint.
    OidcOptions -> Maybe Text
tokenEndpoint :: Prelude.Maybe Prelude.Text,
    -- | The OIDC user info endpoint.
    OidcOptions -> Maybe Text
userInfoEndpoint :: Prelude.Maybe Prelude.Text
  }
  deriving (OidcOptions -> OidcOptions -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: OidcOptions -> OidcOptions -> Bool
$c/= :: OidcOptions -> OidcOptions -> Bool
== :: OidcOptions -> OidcOptions -> Bool
$c== :: OidcOptions -> OidcOptions -> Bool
Prelude.Eq, ReadPrec [OidcOptions]
ReadPrec OidcOptions
Int -> ReadS OidcOptions
ReadS [OidcOptions]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [OidcOptions]
$creadListPrec :: ReadPrec [OidcOptions]
readPrec :: ReadPrec OidcOptions
$creadPrec :: ReadPrec OidcOptions
readList :: ReadS [OidcOptions]
$creadList :: ReadS [OidcOptions]
readsPrec :: Int -> ReadS OidcOptions
$creadsPrec :: Int -> ReadS OidcOptions
Prelude.Read, Int -> OidcOptions -> ShowS
[OidcOptions] -> ShowS
OidcOptions -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [OidcOptions] -> ShowS
$cshowList :: [OidcOptions] -> ShowS
show :: OidcOptions -> String
$cshow :: OidcOptions -> String
showsPrec :: Int -> OidcOptions -> ShowS
$cshowsPrec :: Int -> OidcOptions -> ShowS
Prelude.Show, forall x. Rep OidcOptions x -> OidcOptions
forall x. OidcOptions -> Rep OidcOptions x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep OidcOptions x -> OidcOptions
$cfrom :: forall x. OidcOptions -> Rep OidcOptions x
Prelude.Generic)

-- |
-- Create a value of 'OidcOptions' 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:
--
-- 'authorizationEndpoint', 'oidcOptions_authorizationEndpoint' - The OIDC authorization endpoint.
--
-- 'clientId', 'oidcOptions_clientId' - The client identifier.
--
-- 'clientSecret', 'oidcOptions_clientSecret' - The client secret.
--
-- 'issuer', 'oidcOptions_issuer' - The OIDC issuer.
--
-- 'scope', 'oidcOptions_scope' - The OpenID Connect (OIDC) scope specified.
--
-- 'tokenEndpoint', 'oidcOptions_tokenEndpoint' - The OIDC token endpoint.
--
-- 'userInfoEndpoint', 'oidcOptions_userInfoEndpoint' - The OIDC user info endpoint.
newOidcOptions ::
  OidcOptions
newOidcOptions :: OidcOptions
newOidcOptions =
  OidcOptions'
    { $sel:authorizationEndpoint:OidcOptions' :: Maybe Text
authorizationEndpoint =
        forall a. Maybe a
Prelude.Nothing,
      $sel:clientId:OidcOptions' :: Maybe Text
clientId = forall a. Maybe a
Prelude.Nothing,
      $sel:clientSecret:OidcOptions' :: Maybe Text
clientSecret = forall a. Maybe a
Prelude.Nothing,
      $sel:issuer:OidcOptions' :: Maybe Text
issuer = forall a. Maybe a
Prelude.Nothing,
      $sel:scope:OidcOptions' :: Maybe Text
scope = forall a. Maybe a
Prelude.Nothing,
      $sel:tokenEndpoint:OidcOptions' :: Maybe Text
tokenEndpoint = forall a. Maybe a
Prelude.Nothing,
      $sel:userInfoEndpoint:OidcOptions' :: Maybe Text
userInfoEndpoint = forall a. Maybe a
Prelude.Nothing
    }

-- | The OIDC authorization endpoint.
oidcOptions_authorizationEndpoint :: Lens.Lens' OidcOptions (Prelude.Maybe Prelude.Text)
oidcOptions_authorizationEndpoint :: Lens' OidcOptions (Maybe Text)
oidcOptions_authorizationEndpoint = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\OidcOptions' {Maybe Text
authorizationEndpoint :: Maybe Text
$sel:authorizationEndpoint:OidcOptions' :: OidcOptions -> Maybe Text
authorizationEndpoint} -> Maybe Text
authorizationEndpoint) (\s :: OidcOptions
s@OidcOptions' {} Maybe Text
a -> OidcOptions
s {$sel:authorizationEndpoint:OidcOptions' :: Maybe Text
authorizationEndpoint = Maybe Text
a} :: OidcOptions)

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

-- | The client secret.
oidcOptions_clientSecret :: Lens.Lens' OidcOptions (Prelude.Maybe Prelude.Text)
oidcOptions_clientSecret :: Lens' OidcOptions (Maybe Text)
oidcOptions_clientSecret = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\OidcOptions' {Maybe Text
clientSecret :: Maybe Text
$sel:clientSecret:OidcOptions' :: OidcOptions -> Maybe Text
clientSecret} -> Maybe Text
clientSecret) (\s :: OidcOptions
s@OidcOptions' {} Maybe Text
a -> OidcOptions
s {$sel:clientSecret:OidcOptions' :: Maybe Text
clientSecret = Maybe Text
a} :: OidcOptions)

-- | The OIDC issuer.
oidcOptions_issuer :: Lens.Lens' OidcOptions (Prelude.Maybe Prelude.Text)
oidcOptions_issuer :: Lens' OidcOptions (Maybe Text)
oidcOptions_issuer = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\OidcOptions' {Maybe Text
issuer :: Maybe Text
$sel:issuer:OidcOptions' :: OidcOptions -> Maybe Text
issuer} -> Maybe Text
issuer) (\s :: OidcOptions
s@OidcOptions' {} Maybe Text
a -> OidcOptions
s {$sel:issuer:OidcOptions' :: Maybe Text
issuer = Maybe Text
a} :: OidcOptions)

-- | The OpenID Connect (OIDC) scope specified.
oidcOptions_scope :: Lens.Lens' OidcOptions (Prelude.Maybe Prelude.Text)
oidcOptions_scope :: Lens' OidcOptions (Maybe Text)
oidcOptions_scope = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\OidcOptions' {Maybe Text
scope :: Maybe Text
$sel:scope:OidcOptions' :: OidcOptions -> Maybe Text
scope} -> Maybe Text
scope) (\s :: OidcOptions
s@OidcOptions' {} Maybe Text
a -> OidcOptions
s {$sel:scope:OidcOptions' :: Maybe Text
scope = Maybe Text
a} :: OidcOptions)

-- | The OIDC token endpoint.
oidcOptions_tokenEndpoint :: Lens.Lens' OidcOptions (Prelude.Maybe Prelude.Text)
oidcOptions_tokenEndpoint :: Lens' OidcOptions (Maybe Text)
oidcOptions_tokenEndpoint = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\OidcOptions' {Maybe Text
tokenEndpoint :: Maybe Text
$sel:tokenEndpoint:OidcOptions' :: OidcOptions -> Maybe Text
tokenEndpoint} -> Maybe Text
tokenEndpoint) (\s :: OidcOptions
s@OidcOptions' {} Maybe Text
a -> OidcOptions
s {$sel:tokenEndpoint:OidcOptions' :: Maybe Text
tokenEndpoint = Maybe Text
a} :: OidcOptions)

-- | The OIDC user info endpoint.
oidcOptions_userInfoEndpoint :: Lens.Lens' OidcOptions (Prelude.Maybe Prelude.Text)
oidcOptions_userInfoEndpoint :: Lens' OidcOptions (Maybe Text)
oidcOptions_userInfoEndpoint = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\OidcOptions' {Maybe Text
userInfoEndpoint :: Maybe Text
$sel:userInfoEndpoint:OidcOptions' :: OidcOptions -> Maybe Text
userInfoEndpoint} -> Maybe Text
userInfoEndpoint) (\s :: OidcOptions
s@OidcOptions' {} Maybe Text
a -> OidcOptions
s {$sel:userInfoEndpoint:OidcOptions' :: Maybe Text
userInfoEndpoint = Maybe Text
a} :: OidcOptions)

instance Data.FromXML OidcOptions where
  parseXML :: [Node] -> Either String OidcOptions
parseXML [Node]
x =
    Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> OidcOptions
OidcOptions'
      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
"authorizationEndpoint")
      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
"clientId")
      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
"clientSecret")
      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
"issuer")
      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
"scope")
      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
"tokenEndpoint")
      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
"userInfoEndpoint")

instance Prelude.Hashable OidcOptions where
  hashWithSalt :: Int -> OidcOptions -> Int
hashWithSalt Int
_salt OidcOptions' {Maybe Text
userInfoEndpoint :: Maybe Text
tokenEndpoint :: Maybe Text
scope :: Maybe Text
issuer :: Maybe Text
clientSecret :: Maybe Text
clientId :: Maybe Text
authorizationEndpoint :: Maybe Text
$sel:userInfoEndpoint:OidcOptions' :: OidcOptions -> Maybe Text
$sel:tokenEndpoint:OidcOptions' :: OidcOptions -> Maybe Text
$sel:scope:OidcOptions' :: OidcOptions -> Maybe Text
$sel:issuer:OidcOptions' :: OidcOptions -> Maybe Text
$sel:clientSecret:OidcOptions' :: OidcOptions -> Maybe Text
$sel:clientId:OidcOptions' :: OidcOptions -> Maybe Text
$sel:authorizationEndpoint:OidcOptions' :: OidcOptions -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
authorizationEndpoint
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
clientId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
clientSecret
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
issuer
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
scope
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
tokenEndpoint
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
userInfoEndpoint

instance Prelude.NFData OidcOptions where
  rnf :: OidcOptions -> ()
rnf OidcOptions' {Maybe Text
userInfoEndpoint :: Maybe Text
tokenEndpoint :: Maybe Text
scope :: Maybe Text
issuer :: Maybe Text
clientSecret :: Maybe Text
clientId :: Maybe Text
authorizationEndpoint :: Maybe Text
$sel:userInfoEndpoint:OidcOptions' :: OidcOptions -> Maybe Text
$sel:tokenEndpoint:OidcOptions' :: OidcOptions -> Maybe Text
$sel:scope:OidcOptions' :: OidcOptions -> Maybe Text
$sel:issuer:OidcOptions' :: OidcOptions -> Maybe Text
$sel:clientSecret:OidcOptions' :: OidcOptions -> Maybe Text
$sel:clientId:OidcOptions' :: OidcOptions -> Maybe Text
$sel:authorizationEndpoint:OidcOptions' :: OidcOptions -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
authorizationEndpoint
      seq :: forall a b. a -> b -> b
`Prelude.seq` 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
clientSecret
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
issuer
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
scope
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
tokenEndpoint
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
userInfoEndpoint