module OpenID.Connect.Registration
( Registration(..)
, defaultRegistration
, ClientMetadata
, BasicRegistration(..)
, clientMetadata
, RegistrationResponse(..)
, ClientMetadataResponse
, clientSecretsFromResponse
, additionalMetadataFromResponse
, registrationFromResponse
, (:*:)
, URI(..)
) where
import Crypto.JOSE (JWKSet)
import qualified Crypto.JOSE.JWA.JWE.Alg as JWE
import qualified Crypto.JOSE.JWA.JWS as JWS
import Crypto.JWT (NumericDate)
import qualified Data.Aeson as Aeson
import Data.List.NonEmpty (NonEmpty(..))
import Data.Text (Text)
import GHC.Generics (Generic)
import qualified Network.URI as Network
import OpenID.Connect.Authentication
import OpenID.Connect.JSON
data Registration = Registration
{ Registration -> NonEmpty URI
redirectUris :: NonEmpty URI
, Registration -> Maybe (NonEmpty Text)
responseTypes :: Maybe (NonEmpty Text)
, Registration -> Maybe (NonEmpty Text)
grantTypes :: Maybe (NonEmpty Text)
, Registration -> Maybe Text
applicationType :: Maybe Text
, Registration -> Maybe (NonEmpty Text)
contacts :: Maybe (NonEmpty Text)
, Registration -> Maybe Text
clientName :: Maybe Text
, Registration -> Maybe URI
logoUri :: Maybe URI
, Registration -> Maybe URI
clientUri :: Maybe URI
, Registration -> Maybe URI
policyUri :: Maybe URI
, Registration -> Maybe URI
tosUri :: Maybe URI
, Registration -> Maybe URI
jwksUri :: Maybe URI
, Registration -> Maybe JWKSet
jwks :: Maybe JWKSet
, Registration -> Maybe URI
sectorIdentifierUri :: Maybe URI
, Registration -> Maybe Text
subjectType :: Maybe Text
, Registration -> Maybe Alg
idTokenSignedResponseAlg :: Maybe JWS.Alg
, Registration -> Maybe Alg
idTokenEncryptedResponseAlg :: Maybe JWE.Alg
, Registration -> Maybe Alg
idTokenEncryptedResponseEnc :: Maybe JWE.Alg
, Registration -> Maybe Alg
userinfoSignedResponseAlg :: Maybe JWS.Alg
, Registration -> Maybe Alg
userinfoEncryptedResponseAlg :: Maybe JWE.Alg
, Registration -> Maybe Alg
userinfoEncryptedResponseEnc :: Maybe JWE.Alg
, Registration -> Maybe Alg
requestObjectSigningAlg :: Maybe JWS.Alg
, Registration -> Maybe Alg
requestObjectEncryptionAlg :: Maybe JWE.Alg
, Registration -> Maybe Alg
requestObjectEncryptionEnc :: Maybe JWE.Alg
, Registration -> ClientAuthentication
tokenEndpointAuthMethod :: ClientAuthentication
, Registration -> Maybe Alg
tokenEndpointAuthSigningAlg :: Maybe JWS.Alg
, Registration -> Maybe Int
defaultMaxAge :: Maybe Int
, Registration -> Maybe Bool
requireAuthTime :: Maybe Bool
, Registration -> Maybe (NonEmpty Text)
defaultAcrValues :: Maybe (NonEmpty Text)
, Registration -> Maybe URI
initiateLoginUri :: Maybe URI
, Registration -> Maybe (NonEmpty URI)
requestUris :: Maybe (NonEmpty URI)
}
deriving stock ((forall x. Registration -> Rep Registration x)
-> (forall x. Rep Registration x -> Registration)
-> Generic Registration
forall x. Rep Registration x -> Registration
forall x. Registration -> Rep Registration x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Registration x -> Registration
$cfrom :: forall x. Registration -> Rep Registration x
Generic, Int -> Registration -> ShowS
[Registration] -> ShowS
Registration -> String
(Int -> Registration -> ShowS)
-> (Registration -> String)
-> ([Registration] -> ShowS)
-> Show Registration
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Registration] -> ShowS
$cshowList :: [Registration] -> ShowS
show :: Registration -> String
$cshow :: Registration -> String
showsPrec :: Int -> Registration -> ShowS
$cshowsPrec :: Int -> Registration -> ShowS
Show)
deriving ([Registration] -> Encoding
[Registration] -> Value
Registration -> Encoding
Registration -> Value
(Registration -> Value)
-> (Registration -> Encoding)
-> ([Registration] -> Value)
-> ([Registration] -> Encoding)
-> ToJSON Registration
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [Registration] -> Encoding
$ctoEncodingList :: [Registration] -> Encoding
toJSONList :: [Registration] -> Value
$ctoJSONList :: [Registration] -> Value
toEncoding :: Registration -> Encoding
$ctoEncoding :: Registration -> Encoding
toJSON :: Registration -> Value
$ctoJSON :: Registration -> Value
ToJSON, Value -> Parser [Registration]
Value -> Parser Registration
(Value -> Parser Registration)
-> (Value -> Parser [Registration]) -> FromJSON Registration
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [Registration]
$cparseJSONList :: Value -> Parser [Registration]
parseJSON :: Value -> Parser Registration
$cparseJSON :: Value -> Parser Registration
FromJSON) via GenericJSON Registration
defaultRegistration :: Network.URI -> Registration
defaultRegistration :: URI -> Registration
defaultRegistration URI
redir =
Registration :: NonEmpty URI
-> Maybe (NonEmpty Text)
-> Maybe (NonEmpty Text)
-> Maybe Text
-> Maybe (NonEmpty Text)
-> Maybe Text
-> Maybe URI
-> Maybe URI
-> Maybe URI
-> Maybe URI
-> Maybe URI
-> Maybe JWKSet
-> Maybe URI
-> Maybe Text
-> Maybe Alg
-> Maybe Alg
-> Maybe Alg
-> Maybe Alg
-> Maybe Alg
-> Maybe Alg
-> Maybe Alg
-> Maybe Alg
-> Maybe Alg
-> ClientAuthentication
-> Maybe Alg
-> Maybe Int
-> Maybe Bool
-> Maybe (NonEmpty Text)
-> Maybe URI
-> Maybe (NonEmpty URI)
-> Registration
Registration
{ redirectUris :: NonEmpty URI
redirectUris = URI -> URI
URI URI
redir URI -> [URI] -> NonEmpty URI
forall a. a -> [a] -> NonEmpty a
:| []
, responseTypes :: Maybe (NonEmpty Text)
responseTypes = Maybe (NonEmpty Text)
forall a. Maybe a
Nothing
, grantTypes :: Maybe (NonEmpty Text)
grantTypes = Maybe (NonEmpty Text)
forall a. Maybe a
Nothing
, applicationType :: Maybe Text
applicationType = Maybe Text
forall a. Maybe a
Nothing
, contacts :: Maybe (NonEmpty Text)
contacts = Maybe (NonEmpty Text)
forall a. Maybe a
Nothing
, clientName :: Maybe Text
clientName = Maybe Text
forall a. Maybe a
Nothing
, logoUri :: Maybe URI
logoUri = Maybe URI
forall a. Maybe a
Nothing
, clientUri :: Maybe URI
clientUri = Maybe URI
forall a. Maybe a
Nothing
, policyUri :: Maybe URI
policyUri = Maybe URI
forall a. Maybe a
Nothing
, tosUri :: Maybe URI
tosUri = Maybe URI
forall a. Maybe a
Nothing
, jwksUri :: Maybe URI
jwksUri = Maybe URI
forall a. Maybe a
Nothing
, jwks :: Maybe JWKSet
jwks = Maybe JWKSet
forall a. Maybe a
Nothing
, sectorIdentifierUri :: Maybe URI
sectorIdentifierUri = Maybe URI
forall a. Maybe a
Nothing
, subjectType :: Maybe Text
subjectType = Maybe Text
forall a. Maybe a
Nothing
, idTokenSignedResponseAlg :: Maybe Alg
idTokenSignedResponseAlg = Maybe Alg
forall a. Maybe a
Nothing
, idTokenEncryptedResponseAlg :: Maybe Alg
idTokenEncryptedResponseAlg = Maybe Alg
forall a. Maybe a
Nothing
, idTokenEncryptedResponseEnc :: Maybe Alg
idTokenEncryptedResponseEnc = Maybe Alg
forall a. Maybe a
Nothing
, userinfoSignedResponseAlg :: Maybe Alg
userinfoSignedResponseAlg = Maybe Alg
forall a. Maybe a
Nothing
, userinfoEncryptedResponseAlg :: Maybe Alg
userinfoEncryptedResponseAlg = Maybe Alg
forall a. Maybe a
Nothing
, userinfoEncryptedResponseEnc :: Maybe Alg
userinfoEncryptedResponseEnc = Maybe Alg
forall a. Maybe a
Nothing
, requestObjectSigningAlg :: Maybe Alg
requestObjectSigningAlg = Maybe Alg
forall a. Maybe a
Nothing
, requestObjectEncryptionAlg :: Maybe Alg
requestObjectEncryptionAlg = Maybe Alg
forall a. Maybe a
Nothing
, requestObjectEncryptionEnc :: Maybe Alg
requestObjectEncryptionEnc = Maybe Alg
forall a. Maybe a
Nothing
, tokenEndpointAuthMethod :: ClientAuthentication
tokenEndpointAuthMethod = ClientAuthentication
ClientSecretBasic
, tokenEndpointAuthSigningAlg :: Maybe Alg
tokenEndpointAuthSigningAlg = Maybe Alg
forall a. Maybe a
Nothing
, defaultMaxAge :: Maybe Int
defaultMaxAge = Maybe Int
forall a. Maybe a
Nothing
, requireAuthTime :: Maybe Bool
requireAuthTime = Maybe Bool
forall a. Maybe a
Nothing
, defaultAcrValues :: Maybe (NonEmpty Text)
defaultAcrValues = Maybe (NonEmpty Text)
forall a. Maybe a
Nothing
, initiateLoginUri :: Maybe URI
initiateLoginUri = Maybe URI
forall a. Maybe a
Nothing
, requestUris :: Maybe (NonEmpty URI)
requestUris = Maybe (NonEmpty URI)
forall a. Maybe a
Nothing
}
data BasicRegistration = BasicRegistration
instance ToJSON BasicRegistration where
toJSON :: BasicRegistration -> Value
toJSON BasicRegistration
_ = [Pair] -> Value
Aeson.object [ ]
instance FromJSON BasicRegistration where
parseJSON :: Value -> Parser BasicRegistration
parseJSON Value
_ = BasicRegistration -> Parser BasicRegistration
forall (f :: * -> *) a. Applicative f => a -> f a
pure BasicRegistration
BasicRegistration
type ClientMetadata a = Registration :*: a
clientMetadata :: Registration -> a -> ClientMetadata a
clientMetadata :: Registration -> a -> ClientMetadata a
clientMetadata Registration
r a
a = (Registration, a) -> ClientMetadata a
forall a b. (a, b) -> a :*: b
Join (Registration
r, a
a)
data RegistrationResponse = RegistrationResponse
{ RegistrationResponse -> Text
clientId :: Text
, RegistrationResponse -> Maybe Text
clientSecret :: Maybe Text
, RegistrationResponse -> Maybe Text
registrationAccessToken :: Maybe Text
, RegistrationResponse -> Maybe URI
registrationClientUri :: Maybe URI
, RegistrationResponse -> Maybe NumericDate
clientIdIssuedAt :: Maybe NumericDate
, RegistrationResponse -> Maybe NumericDate
clientSecretExpiresAt :: Maybe NumericDate
}
deriving stock ((forall x. RegistrationResponse -> Rep RegistrationResponse x)
-> (forall x. Rep RegistrationResponse x -> RegistrationResponse)
-> Generic RegistrationResponse
forall x. Rep RegistrationResponse x -> RegistrationResponse
forall x. RegistrationResponse -> Rep RegistrationResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RegistrationResponse x -> RegistrationResponse
$cfrom :: forall x. RegistrationResponse -> Rep RegistrationResponse x
Generic, Int -> RegistrationResponse -> ShowS
[RegistrationResponse] -> ShowS
RegistrationResponse -> String
(Int -> RegistrationResponse -> ShowS)
-> (RegistrationResponse -> String)
-> ([RegistrationResponse] -> ShowS)
-> Show RegistrationResponse
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RegistrationResponse] -> ShowS
$cshowList :: [RegistrationResponse] -> ShowS
show :: RegistrationResponse -> String
$cshow :: RegistrationResponse -> String
showsPrec :: Int -> RegistrationResponse -> ShowS
$cshowsPrec :: Int -> RegistrationResponse -> ShowS
Show)
deriving ([RegistrationResponse] -> Encoding
[RegistrationResponse] -> Value
RegistrationResponse -> Encoding
RegistrationResponse -> Value
(RegistrationResponse -> Value)
-> (RegistrationResponse -> Encoding)
-> ([RegistrationResponse] -> Value)
-> ([RegistrationResponse] -> Encoding)
-> ToJSON RegistrationResponse
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [RegistrationResponse] -> Encoding
$ctoEncodingList :: [RegistrationResponse] -> Encoding
toJSONList :: [RegistrationResponse] -> Value
$ctoJSONList :: [RegistrationResponse] -> Value
toEncoding :: RegistrationResponse -> Encoding
$ctoEncoding :: RegistrationResponse -> Encoding
toJSON :: RegistrationResponse -> Value
$ctoJSON :: RegistrationResponse -> Value
ToJSON, Value -> Parser [RegistrationResponse]
Value -> Parser RegistrationResponse
(Value -> Parser RegistrationResponse)
-> (Value -> Parser [RegistrationResponse])
-> FromJSON RegistrationResponse
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [RegistrationResponse]
$cparseJSONList :: Value -> Parser [RegistrationResponse]
parseJSON :: Value -> Parser RegistrationResponse
$cparseJSON :: Value -> Parser RegistrationResponse
FromJSON) via GenericJSON RegistrationResponse
type ClientMetadataResponse a = Registration :*: RegistrationResponse :*: a
registrationFromResponse :: ClientMetadataResponse a -> Registration
registrationFromResponse :: ClientMetadataResponse a -> Registration
registrationFromResponse (Join (Join (Registration
r, RegistrationResponse
_), a
_)) = Registration
r
additionalMetadataFromResponse :: ClientMetadataResponse a -> a
additionalMetadataFromResponse :: ClientMetadataResponse a -> a
additionalMetadataFromResponse (Join (Registration :*: RegistrationResponse
_, a
a)) = a
a
clientSecretsFromResponse :: ClientMetadataResponse a -> RegistrationResponse
clientSecretsFromResponse :: ClientMetadataResponse a -> RegistrationResponse
clientSecretsFromResponse (Join (Join (Registration
_, RegistrationResponse
r), a
_)) = RegistrationResponse
r