|
1 | 1 | {-# LANGUAGE FlexibleContexts #-}
|
2 | 2 | {-# LANGUAGE OverloadedStrings #-}
|
3 | 3 | {-# LANGUAGE RecordWildCards #-}
|
| 4 | +{-# LANGUAGE LambdaCase #-} |
| 5 | +{-# LANGUAGE CPP #-} |
4 | 6 | module Kubernetes.Client.Auth.OIDC
|
5 | 7 | (oidcAuth, OIDCCache, cachedOIDCAuth)
|
6 | 8 | where
|
7 | 9 |
|
8 | 10 | import Control.Applicative
|
9 | 11 | import Control.Concurrent.STM
|
10 | 12 | import Control.Exception.Safe (Exception, throwM)
|
| 13 | +import Control.Monad.Except (runExceptT) |
11 | 14 | import Data.Either.Combinators
|
12 | 15 | import Data.Function ((&))
|
13 | 16 | import Data.Map (Map)
|
14 | 17 | import Data.Maybe
|
15 | 18 | import Data.Monoid ((<>))
|
16 | 19 | import Data.Text
|
| 20 | +import Data.Text.Encoding (encodeUtf8) |
17 | 21 | import Data.Time.Clock.POSIX (getPOSIXTime)
|
18 | 22 | import Jose.Jwt
|
19 | 23 | import Kubernetes.Client.Auth.Internal.Types
|
@@ -41,6 +45,9 @@ data OIDCAuth = OIDCAuth { issuerURL :: Text
|
41 | 45 | , tlsParams :: TLS.ClientParams
|
42 | 46 | , idTokenTVar :: TVar(Maybe Text)
|
43 | 47 | , refreshTokenTVar :: TVar(Maybe Text)
|
| 48 | +#if MIN_VERSION_hoauth2(2,3,0) |
| 49 | + , redirectUri :: URI |
| 50 | +#endif |
44 | 51 | }
|
45 | 52 |
|
46 | 53 | -- | Cache OIDCAuth based on issuerURL and clientID.
|
@@ -93,14 +100,43 @@ fetchToken auth@(OIDCAuth{..}) = do
|
93 | 100 | tokenEndpoint <- fetchTokenEndpoint mgr auth
|
94 | 101 | tokenURI <- parseURI strictURIParserOptions (Text.encodeUtf8 tokenEndpoint)
|
95 | 102 | & either (throwM . OIDCURIException) pure
|
| 103 | + |
| 104 | +#if MIN_VERSION_hoauth2(2,3,0) |
| 105 | + let oauth = OAuth2{ oauth2ClientId = clientID |
| 106 | + , oauth2ClientSecret = clientSecret |
| 107 | + , oauth2AuthorizeEndpoint = tokenURI |
| 108 | + , oauth2TokenEndpoint = tokenURI |
| 109 | + , oauth2RedirectUri = redirectUri |
| 110 | + } |
| 111 | +#elif MIN_VERSION_hoauth2(2,2,0) |
| 112 | + let oauth = OAuth2{ oauth2ClientId = clientID |
| 113 | + , oauth2ClientSecret = clientSecret |
| 114 | + , oauth2AuthorizeEndpoint = tokenURI |
| 115 | + , oauth2TokenEndpoint = tokenURI |
| 116 | + , oauth2RedirectUri = Nothing |
| 117 | + } |
| 118 | +#elif MIN_VERSION_hoauth2(2,0,0) |
| 119 | + let oauth = OAuth2{ oauth2ClientId = clientID |
| 120 | + , oauth2ClientSecret = Just clientSecret |
| 121 | + , oauth2AuthorizeEndpoint = tokenURI |
| 122 | + , oauth2TokenEndpoint = tokenURI |
| 123 | + , oauth2RedirectUri = Nothing |
| 124 | + } |
| 125 | +#else |
96 | 126 | let oauth = OAuth2{ oauthClientId = clientID
|
97 | 127 | , oauthClientSecret = Just clientSecret
|
98 | 128 | , oauthAccessTokenEndpoint = tokenURI
|
99 | 129 | , oauthOAuthorizeEndpoint = tokenURI
|
100 | 130 | , oauthCallback = Nothing
|
101 | 131 | }
|
102 |
| - oauthToken <- refreshAccessToken mgr oauth (RefreshToken token) |
103 |
| - >>= either (throwM . OIDCOAuthException) pure |
| 132 | +#endif |
| 133 | + |
| 134 | +#if MIN_VERSION_hoauth2(2,2,0) |
| 135 | + oauthToken <- runExceptT (refreshAccessToken mgr oauth (RefreshToken token)) >>= either (throwM . OIDCOAuthException) pure |
| 136 | +#else |
| 137 | + oauthToken <- (refreshAccessToken mgr oauth (RefreshToken token)) >>= either (throwM . OIDCOAuthException) pure |
| 138 | +#endif |
| 139 | + |
104 | 140 | case OAuth.idToken oauthToken of
|
105 | 141 | Nothing -> throwM $ OIDCGetTokenException "token response did not contain an id_token, either the scope \"openid\" wasn't requested upon login, or the provider doesn't support id_tokens as part of the refresh response."
|
106 | 142 | Just (IdToken t) -> do
|
@@ -152,6 +188,15 @@ parseOIDCAuthInfo authInfo = do
|
152 | 188 | eitherTLSParams <- parseCA authInfo
|
153 | 189 | idTokenTVar <- atomically $ newTVar $ Map.lookup "id-token" authInfo
|
154 | 190 | refreshTokenTVar <- atomically $ newTVar $ Map.lookup "refresh-token" authInfo
|
| 191 | + |
| 192 | +#if MIN_VERSION_hoauth2(2,3,0) |
| 193 | + redirectUri <- case Map.lookup "redirect-uri" authInfo of |
| 194 | + Nothing -> throwM $ OIDCAuthMissingInformation "redirect-uri" |
| 195 | + Just raw -> case parseURI laxURIParserOptions $ encodeUtf8 raw of |
| 196 | + Left err -> throwM $ OIDCAuthMissingInformation ("Couldn't parse redirect URI: " <> show err) |
| 197 | + Right x -> return x |
| 198 | +#endif |
| 199 | + |
155 | 200 | return $ do
|
156 | 201 | tlsParams <- mapLeft OIDCAuthCAParsingFailed eitherTLSParams
|
157 | 202 | issuerURL <- lookupEither "idp-issuer-url"
|
|
0 commit comments