{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TemplateHaskell #-}
module Web.OIDC.Client.Discovery.Provider
(
Provider(..)
, Configuration(..)
, JwsAlgJson(..)
) where
import Data.Aeson (FromJSON, parseJSON, withText)
import Data.Aeson.TH (Options (..), defaultOptions,
deriveFromJSON)
import Data.Aeson.Types (camelTo2)
import Data.Text (Text)
import Jose.Jwa (JwsAlg (..))
import Jose.Jwk (Jwk)
import Web.OIDC.Client.Types (IssuerLocation, ScopeValue)
data Provider = Provider { Provider -> Configuration
configuration :: Configuration, Provider -> [Jwk]
jwkSet :: [Jwk] }
data JwsAlgJson = JwsAlgJson { JwsAlgJson -> JwsAlg
getJwsAlg :: JwsAlg } | Unsupported Text deriving (Int -> JwsAlgJson -> ShowS
[JwsAlgJson] -> ShowS
JwsAlgJson -> String
(Int -> JwsAlgJson -> ShowS)
-> (JwsAlgJson -> String)
-> ([JwsAlgJson] -> ShowS)
-> Show JwsAlgJson
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [JwsAlgJson] -> ShowS
$cshowList :: [JwsAlgJson] -> ShowS
show :: JwsAlgJson -> String
$cshow :: JwsAlgJson -> String
showsPrec :: Int -> JwsAlgJson -> ShowS
$cshowsPrec :: Int -> JwsAlgJson -> ShowS
Show, JwsAlgJson -> JwsAlgJson -> Bool
(JwsAlgJson -> JwsAlgJson -> Bool)
-> (JwsAlgJson -> JwsAlgJson -> Bool) -> Eq JwsAlgJson
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: JwsAlgJson -> JwsAlgJson -> Bool
$c/= :: JwsAlgJson -> JwsAlgJson -> Bool
== :: JwsAlgJson -> JwsAlgJson -> Bool
$c== :: JwsAlgJson -> JwsAlgJson -> Bool
Eq)
instance FromJSON JwsAlgJson where
parseJSON :: Value -> Parser JwsAlgJson
parseJSON = String -> (Text -> Parser JwsAlgJson) -> Value -> Parser JwsAlgJson
forall a. String -> (Text -> Parser a) -> Value -> Parser a
withText String
"JwsAlgJson" ((Text -> Parser JwsAlgJson) -> Value -> Parser JwsAlgJson)
-> (Text -> Parser JwsAlgJson) -> Value -> Parser JwsAlgJson
forall a b. (a -> b) -> a -> b
$ \case
Text
"HS256" -> JwsAlgJson -> Parser JwsAlgJson
forall (f :: * -> *) a. Applicative f => a -> f a
pure (JwsAlgJson -> Parser JwsAlgJson)
-> JwsAlgJson -> Parser JwsAlgJson
forall a b. (a -> b) -> a -> b
$ JwsAlg -> JwsAlgJson
JwsAlgJson JwsAlg
HS256
Text
"HS384" -> JwsAlgJson -> Parser JwsAlgJson
forall (f :: * -> *) a. Applicative f => a -> f a
pure (JwsAlgJson -> Parser JwsAlgJson)
-> JwsAlgJson -> Parser JwsAlgJson
forall a b. (a -> b) -> a -> b
$ JwsAlg -> JwsAlgJson
JwsAlgJson JwsAlg
HS384
Text
"HS512" -> JwsAlgJson -> Parser JwsAlgJson
forall (f :: * -> *) a. Applicative f => a -> f a
pure (JwsAlgJson -> Parser JwsAlgJson)
-> JwsAlgJson -> Parser JwsAlgJson
forall a b. (a -> b) -> a -> b
$ JwsAlg -> JwsAlgJson
JwsAlgJson JwsAlg
HS512
Text
"RS256" -> JwsAlgJson -> Parser JwsAlgJson
forall (f :: * -> *) a. Applicative f => a -> f a
pure (JwsAlgJson -> Parser JwsAlgJson)
-> JwsAlgJson -> Parser JwsAlgJson
forall a b. (a -> b) -> a -> b
$ JwsAlg -> JwsAlgJson
JwsAlgJson JwsAlg
RS256
Text
"RS384" -> JwsAlgJson -> Parser JwsAlgJson
forall (f :: * -> *) a. Applicative f => a -> f a
pure (JwsAlgJson -> Parser JwsAlgJson)
-> JwsAlgJson -> Parser JwsAlgJson
forall a b. (a -> b) -> a -> b
$ JwsAlg -> JwsAlgJson
JwsAlgJson JwsAlg
RS384
Text
"RS512" -> JwsAlgJson -> Parser JwsAlgJson
forall (f :: * -> *) a. Applicative f => a -> f a
pure (JwsAlgJson -> Parser JwsAlgJson)
-> JwsAlgJson -> Parser JwsAlgJson
forall a b. (a -> b) -> a -> b
$ JwsAlg -> JwsAlgJson
JwsAlgJson JwsAlg
RS512
Text
"ES256" -> JwsAlgJson -> Parser JwsAlgJson
forall (f :: * -> *) a. Applicative f => a -> f a
pure (JwsAlgJson -> Parser JwsAlgJson)
-> JwsAlgJson -> Parser JwsAlgJson
forall a b. (a -> b) -> a -> b
$ JwsAlg -> JwsAlgJson
JwsAlgJson JwsAlg
ES256
Text
"ES384" -> JwsAlgJson -> Parser JwsAlgJson
forall (f :: * -> *) a. Applicative f => a -> f a
pure (JwsAlgJson -> Parser JwsAlgJson)
-> JwsAlgJson -> Parser JwsAlgJson
forall a b. (a -> b) -> a -> b
$ JwsAlg -> JwsAlgJson
JwsAlgJson JwsAlg
ES384
Text
"ES512" -> JwsAlgJson -> Parser JwsAlgJson
forall (f :: * -> *) a. Applicative f => a -> f a
pure (JwsAlgJson -> Parser JwsAlgJson)
-> JwsAlgJson -> Parser JwsAlgJson
forall a b. (a -> b) -> a -> b
$ JwsAlg -> JwsAlgJson
JwsAlgJson JwsAlg
ES512
Text
"none" -> JwsAlgJson -> Parser JwsAlgJson
forall (f :: * -> *) a. Applicative f => a -> f a
pure (JwsAlgJson -> Parser JwsAlgJson)
-> JwsAlgJson -> Parser JwsAlgJson
forall a b. (a -> b) -> a -> b
$ JwsAlg -> JwsAlgJson
JwsAlgJson JwsAlg
None
Text
other -> JwsAlgJson -> Parser JwsAlgJson
forall (f :: * -> *) a. Applicative f => a -> f a
pure (JwsAlgJson -> Parser JwsAlgJson)
-> JwsAlgJson -> Parser JwsAlgJson
forall a b. (a -> b) -> a -> b
$ Text -> JwsAlgJson
Unsupported Text
other
data Configuration = Configuration
{ Configuration -> Text
issuer :: IssuerLocation
, Configuration -> Text
authorizationEndpoint :: Text
, Configuration -> Text
tokenEndpoint :: Text
, Configuration -> Maybe Text
userinfoEndpoint :: Maybe Text
, Configuration -> Maybe Text
revocationEndpoint :: Maybe Text
, Configuration -> Text
jwksUri :: Text
, Configuration -> [Text]
responseTypesSupported :: [Text]
, Configuration -> [Text]
subjectTypesSupported :: [Text]
, Configuration -> [JwsAlgJson]
idTokenSigningAlgValuesSupported :: [JwsAlgJson]
, Configuration -> Maybe [Text]
scopesSupported :: Maybe [ScopeValue]
, Configuration -> Maybe [Text]
tokenEndpointAuthMethodsSupported :: Maybe [Text]
, Configuration -> Maybe [Text]
claimsSupported :: Maybe [Text]
}
deriving (Int -> Configuration -> ShowS
[Configuration] -> ShowS
Configuration -> String
(Int -> Configuration -> ShowS)
-> (Configuration -> String)
-> ([Configuration] -> ShowS)
-> Show Configuration
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Configuration] -> ShowS
$cshowList :: [Configuration] -> ShowS
show :: Configuration -> String
$cshow :: Configuration -> String
showsPrec :: Int -> Configuration -> ShowS
$cshowsPrec :: Int -> Configuration -> ShowS
Show, Configuration -> Configuration -> Bool
(Configuration -> Configuration -> Bool)
-> (Configuration -> Configuration -> Bool) -> Eq Configuration
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Configuration -> Configuration -> Bool
$c/= :: Configuration -> Configuration -> Bool
== :: Configuration -> Configuration -> Bool
$c== :: Configuration -> Configuration -> Bool
Eq)
$(deriveFromJSON defaultOptions{fieldLabelModifier = camelTo2 '_'} ''Configuration)