{-# LANGUAGE FlexibleInstances #-}
module Network.OAuth2.Experiment.Grants.ResourceOwnerPassword where
import Data.Map.Strict (Map)
import Data.Map.Strict qualified as Map
import Data.Set (Set)
import Data.Text.Lazy (Text)
import Network.OAuth.OAuth2 (ClientAuthenticationMethod (..), OAuth2 (..))
import Network.OAuth.OAuth2 qualified as OAuth2
import Network.OAuth2.Experiment.Flows.RefreshTokenRequest
import Network.OAuth2.Experiment.Flows.TokenRequest
import Network.OAuth2.Experiment.Flows.UserInfoRequest
import Network.OAuth2.Experiment.Types
data ResourceOwnerPasswordApplication = ResourceOwnerPasswordApplication
{ ResourceOwnerPasswordApplication -> ClientId
ropClientId :: ClientId
, ResourceOwnerPasswordApplication -> ClientSecret
ropClientSecret :: ClientSecret
, ResourceOwnerPasswordApplication -> Text
ropName :: Text
, ResourceOwnerPasswordApplication -> Set Scope
ropScope :: Set Scope
, ResourceOwnerPasswordApplication -> Username
ropUserName :: Username
, ResourceOwnerPasswordApplication -> Password
ropPassword :: Password
, :: Map Text Text
, ResourceOwnerPasswordApplication -> ClientAuthenticationMethod
ropTokenRequestAuthenticationMethod :: ClientAuthenticationMethod
}
instance HasOAuth2Key ResourceOwnerPasswordApplication where
mkOAuth2Key :: ResourceOwnerPasswordApplication -> OAuth2
mkOAuth2Key :: ResourceOwnerPasswordApplication -> OAuth2
mkOAuth2Key ResourceOwnerPasswordApplication {Map Text Text
Text
Set Scope
ClientAuthenticationMethod
Password
Username
ClientSecret
ClientId
ropClientId :: ResourceOwnerPasswordApplication -> ClientId
ropClientSecret :: ResourceOwnerPasswordApplication -> ClientSecret
ropName :: ResourceOwnerPasswordApplication -> Text
ropScope :: ResourceOwnerPasswordApplication -> Set Scope
ropUserName :: ResourceOwnerPasswordApplication -> Username
ropPassword :: ResourceOwnerPasswordApplication -> Password
ropTokenRequestExtraParams :: ResourceOwnerPasswordApplication -> Map Text Text
ropTokenRequestAuthenticationMethod :: ResourceOwnerPasswordApplication -> ClientAuthenticationMethod
ropClientId :: ClientId
ropClientSecret :: ClientSecret
ropName :: Text
ropScope :: Set Scope
ropUserName :: Username
ropPassword :: Password
ropTokenRequestExtraParams :: Map Text Text
ropTokenRequestAuthenticationMethod :: ClientAuthenticationMethod
..} = ClientId -> ClientSecret -> OAuth2
toOAuth2Key ClientId
ropClientId ClientSecret
ropClientSecret
instance HasTokenRequestClientAuthenticationMethod ResourceOwnerPasswordApplication where
getClientAuthenticationMethod :: ResourceOwnerPasswordApplication -> ClientAuthenticationMethod
getClientAuthenticationMethod :: ResourceOwnerPasswordApplication -> ClientAuthenticationMethod
getClientAuthenticationMethod = ResourceOwnerPasswordApplication -> ClientAuthenticationMethod
ropTokenRequestAuthenticationMethod
instance HasTokenRequest ResourceOwnerPasswordApplication where
type ExchangeTokenInfo ResourceOwnerPasswordApplication = NoNeedExchangeToken
data TokenRequest ResourceOwnerPasswordApplication = PasswordTokenRequest
{ TokenRequest ResourceOwnerPasswordApplication -> Set Scope
trScope :: Set Scope
, TokenRequest ResourceOwnerPasswordApplication -> Username
trUsername :: Username
, TokenRequest ResourceOwnerPasswordApplication -> Password
trPassword :: Password
, TokenRequest ResourceOwnerPasswordApplication -> GrantTypeValue
trGrantType :: GrantTypeValue
, :: Map Text Text
}
mkTokenRequestParam :: ResourceOwnerPasswordApplication -> NoNeedExchangeToken -> TokenRequest ResourceOwnerPasswordApplication
mkTokenRequestParam :: ResourceOwnerPasswordApplication
-> NoNeedExchangeToken
-> TokenRequest ResourceOwnerPasswordApplication
mkTokenRequestParam ResourceOwnerPasswordApplication {Map Text Text
Text
Set Scope
ClientAuthenticationMethod
Password
Username
ClientSecret
ClientId
ropClientId :: ResourceOwnerPasswordApplication -> ClientId
ropClientSecret :: ResourceOwnerPasswordApplication -> ClientSecret
ropName :: ResourceOwnerPasswordApplication -> Text
ropScope :: ResourceOwnerPasswordApplication -> Set Scope
ropUserName :: ResourceOwnerPasswordApplication -> Username
ropPassword :: ResourceOwnerPasswordApplication -> Password
ropTokenRequestExtraParams :: ResourceOwnerPasswordApplication -> Map Text Text
ropTokenRequestAuthenticationMethod :: ResourceOwnerPasswordApplication -> ClientAuthenticationMethod
ropClientId :: ClientId
ropClientSecret :: ClientSecret
ropName :: Text
ropScope :: Set Scope
ropUserName :: Username
ropPassword :: Password
ropTokenRequestExtraParams :: Map Text Text
ropTokenRequestAuthenticationMethod :: ClientAuthenticationMethod
..} NoNeedExchangeToken
_ =
PasswordTokenRequest
{ trUsername :: Username
trUsername = Username
ropUserName
, trPassword :: Password
trPassword = Password
ropPassword
, trGrantType :: GrantTypeValue
trGrantType = GrantTypeValue
GTPassword
, trScope :: Set Scope
trScope = Set Scope
ropScope
, trExtraParams :: Map Text Text
trExtraParams = Map Text Text
ropTokenRequestExtraParams
}
instance ToQueryParam (TokenRequest ResourceOwnerPasswordApplication) where
toQueryParam :: TokenRequest ResourceOwnerPasswordApplication -> Map Text Text
toQueryParam :: TokenRequest ResourceOwnerPasswordApplication -> Map Text Text
toQueryParam PasswordTokenRequest {Map Text Text
Set Scope
Password
Username
GrantTypeValue
trScope :: TokenRequest ResourceOwnerPasswordApplication -> Set Scope
trUsername :: TokenRequest ResourceOwnerPasswordApplication -> Username
trPassword :: TokenRequest ResourceOwnerPasswordApplication -> Password
trGrantType :: TokenRequest ResourceOwnerPasswordApplication -> GrantTypeValue
trExtraParams :: TokenRequest ResourceOwnerPasswordApplication -> Map Text Text
trScope :: Set Scope
trUsername :: Username
trPassword :: Password
trGrantType :: GrantTypeValue
trExtraParams :: Map Text Text
..} =
[Map Text Text] -> Map Text Text
forall (f :: * -> *) k a.
(Foldable f, Ord k) =>
f (Map k a) -> Map k a
Map.unions
[ GrantTypeValue -> Map Text Text
forall a. ToQueryParam a => a -> Map Text Text
toQueryParam GrantTypeValue
trGrantType
, Set Scope -> Map Text Text
forall a. ToQueryParam a => a -> Map Text Text
toQueryParam Set Scope
trScope
, Username -> Map Text Text
forall a. ToQueryParam a => a -> Map Text Text
toQueryParam Username
trUsername
, Password -> Map Text Text
forall a. ToQueryParam a => a -> Map Text Text
toQueryParam Password
trPassword
, Map Text Text
trExtraParams
]
instance HasUserInfoRequest ResourceOwnerPasswordApplication
instance HasRefreshTokenRequest ResourceOwnerPasswordApplication where
mkRefreshTokenRequestParam :: ResourceOwnerPasswordApplication -> OAuth2.RefreshToken -> RefreshTokenRequest
mkRefreshTokenRequestParam :: ResourceOwnerPasswordApplication
-> RefreshToken -> RefreshTokenRequest
mkRefreshTokenRequestParam ResourceOwnerPasswordApplication {Map Text Text
Text
Set Scope
ClientAuthenticationMethod
Password
Username
ClientSecret
ClientId
ropClientId :: ResourceOwnerPasswordApplication -> ClientId
ropClientSecret :: ResourceOwnerPasswordApplication -> ClientSecret
ropName :: ResourceOwnerPasswordApplication -> Text
ropScope :: ResourceOwnerPasswordApplication -> Set Scope
ropUserName :: ResourceOwnerPasswordApplication -> Username
ropPassword :: ResourceOwnerPasswordApplication -> Password
ropTokenRequestExtraParams :: ResourceOwnerPasswordApplication -> Map Text Text
ropTokenRequestAuthenticationMethod :: ResourceOwnerPasswordApplication -> ClientAuthenticationMethod
ropClientId :: ClientId
ropClientSecret :: ClientSecret
ropName :: Text
ropScope :: Set Scope
ropUserName :: Username
ropPassword :: Password
ropTokenRequestExtraParams :: Map Text Text
ropTokenRequestAuthenticationMethod :: ClientAuthenticationMethod
..} RefreshToken
rt =
RefreshTokenRequest
{ rrScope :: Set Scope
rrScope = Set Scope
ropScope
, rrGrantType :: GrantTypeValue
rrGrantType = GrantTypeValue
GTRefreshToken
, rrRefreshToken :: RefreshToken
rrRefreshToken = RefreshToken
rt
, rrClientId :: Maybe ClientId
rrClientId = if ClientAuthenticationMethod
ropTokenRequestAuthenticationMethod ClientAuthenticationMethod -> ClientAuthenticationMethod -> Bool
forall a. Eq a => a -> a -> Bool
== ClientAuthenticationMethod
ClientSecretPost then ClientId -> Maybe ClientId
forall a. a -> Maybe a
Just ClientId
ropClientId else Maybe ClientId
forall a. Maybe a
Nothing
, rrClientSecret :: Maybe ClientSecret
rrClientSecret = if ClientAuthenticationMethod
ropTokenRequestAuthenticationMethod ClientAuthenticationMethod -> ClientAuthenticationMethod -> Bool
forall a. Eq a => a -> a -> Bool
== ClientAuthenticationMethod
ClientSecretPost then ClientSecret -> Maybe ClientSecret
forall a. a -> Maybe a
Just ClientSecret
ropClientSecret else Maybe ClientSecret
forall a. Maybe a
Nothing
}