{-# 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
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
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 = forall a. String -> (Text -> Parser a) -> Value -> Parser a
withText String
"JwsAlgJson" forall a b. (a -> b) -> a -> b
$ \case
Text
"HS256" -> forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ JwsAlg -> JwsAlgJson
JwsAlgJson JwsAlg
HS256
Text
"HS384" -> forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ JwsAlg -> JwsAlgJson
JwsAlgJson JwsAlg
HS384
Text
"HS512" -> forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ JwsAlg -> JwsAlgJson
JwsAlgJson JwsAlg
HS512
Text
"RS256" -> forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ JwsAlg -> JwsAlgJson
JwsAlgJson JwsAlg
RS256
Text
"RS384" -> forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ JwsAlg -> JwsAlgJson
JwsAlgJson JwsAlg
RS384
Text
"RS512" -> forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ JwsAlg -> JwsAlgJson
JwsAlgJson JwsAlg
RS512
Text
"ES256" -> forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ JwsAlg -> JwsAlgJson
JwsAlgJson JwsAlg
ES256
Text
"ES384" -> forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ JwsAlg -> JwsAlgJson
JwsAlgJson JwsAlg
ES384
Text
"ES512" -> forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ JwsAlg -> JwsAlgJson
JwsAlgJson JwsAlg
ES512
Text
"none" -> forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ JwsAlg -> JwsAlgJson
JwsAlgJson JwsAlg
None
Text
other -> forall (f :: * -> *) a. Applicative f => a -> f a
pure 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
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
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)