Remove error calls from OIDC Auth
This commit is contained in:
@@ -7,6 +7,7 @@ where
|
||||
|
||||
import Control.Applicative
|
||||
import Control.Concurrent.STM
|
||||
import Control.Exception.Safe (Exception, throwM)
|
||||
import Data.Either.Combinators
|
||||
import Data.Function ((&))
|
||||
import Data.Map (Map)
|
||||
@@ -19,7 +20,7 @@ import Kubernetes.Client.KubeConfig
|
||||
import Kubernetes.OpenAPI.Core
|
||||
import Network.HTTP.Client
|
||||
import Network.HTTP.Client.TLS
|
||||
import Network.OAuth.OAuth2 as OAuth hiding (error)
|
||||
import Network.OAuth.OAuth2 as OAuth
|
||||
import Network.TLS as TLS
|
||||
import URI.ByteString
|
||||
import Web.JWT as JWT
|
||||
@@ -31,6 +32,7 @@ import qualified Data.Map as Map
|
||||
import qualified Data.Text as Text
|
||||
import qualified Data.Text.Encoding as Text
|
||||
import qualified Lens.Micro as L
|
||||
import qualified Network.OAuth.OAuth2.TokenRequest as OAuth2TokenRequest
|
||||
|
||||
data OIDCAuth = OIDCAuth { issuerURL :: Text
|
||||
, clientID :: Text
|
||||
@@ -50,6 +52,16 @@ instance AuthMethod OIDCAuth where
|
||||
$ setHeader req [("Authorization", "Bearer " <> (Text.encodeUtf8 token))]
|
||||
& L.set rAuthTypesL []
|
||||
|
||||
data OIDCGetTokenException = OIDCOAuthException (OAuth2Error OAuth2TokenRequest.Errors)
|
||||
| OIDCURIException URIParseError
|
||||
| OIDCGetTokenException String
|
||||
deriving Show
|
||||
instance Exception OIDCGetTokenException
|
||||
|
||||
data OIDCAuthParsingException = OIDCAuthParsingException String
|
||||
deriving Show
|
||||
instance Exception OIDCAuthParsingException
|
||||
|
||||
-- TODO: Consider a token expired few seconds before actual expiry to account for time skew
|
||||
getToken :: OIDCAuth -> IO Text
|
||||
getToken o@(OIDCAuth{..}) = do
|
||||
@@ -64,16 +76,17 @@ getToken o@(OIDCAuth{..}) = do
|
||||
isValidToken = fromMaybe False (fmap (now <) maybeExp)
|
||||
if not isValidToken
|
||||
then fetchToken mgr o
|
||||
else return $ fromMaybe (error "impossible") idToken
|
||||
else maybe (throwM $ OIDCGetTokenException "impossible") pure idToken
|
||||
|
||||
fetchToken :: Manager -> OIDCAuth -> IO Text
|
||||
fetchToken mgr o@(OIDCAuth{..}) = do
|
||||
maybeToken <- readTVarIO refreshTokenTVar
|
||||
case maybeToken of
|
||||
Nothing -> error "cannot refresh id-token without a refresh token"
|
||||
Nothing -> throwM $ OIDCGetTokenException "cannot refresh id-token without a refresh token"
|
||||
Just token -> do
|
||||
tokenEndpoint <- fetchTokenEndpoint mgr o
|
||||
tokenURI <- exceptEither $ parseURI strictURIParserOptions (Text.encodeUtf8 tokenEndpoint)
|
||||
tokenURI <- parseURI strictURIParserOptions (Text.encodeUtf8 tokenEndpoint)
|
||||
& either (throwM . OIDCURIException) pure
|
||||
let oauth = OAuth2{ oauthClientId = clientID
|
||||
, oauthClientSecret = clientSecret
|
||||
, oauthAccessTokenEndpoint = tokenURI
|
||||
@@ -81,9 +94,9 @@ fetchToken mgr o@(OIDCAuth{..}) = do
|
||||
, oauthCallback = Nothing
|
||||
}
|
||||
oauthToken <- refreshAccessToken mgr oauth (RefreshToken token)
|
||||
>>= exceptEither
|
||||
>>= either (throwM . OIDCOAuthException) pure
|
||||
case OAuth.idToken oauthToken of
|
||||
Nothing -> error "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."
|
||||
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."
|
||||
Just (IdToken t) -> do
|
||||
_ <- atomically $ writeTVar idTokenTVar (Just t)
|
||||
return t
|
||||
@@ -94,10 +107,6 @@ fetchTokenEndpoint mgr OIDCAuth{..} = do
|
||||
& (fmap configuration)
|
||||
& (fmap tokenEndpoint)
|
||||
|
||||
exceptEither :: Show b => Either b a -> IO a
|
||||
exceptEither (Right a) = pure a
|
||||
exceptEither (Left t) = error (show t)
|
||||
|
||||
{-
|
||||
Detects if auth-provier name is oidc, if it is configures the 'KubernetesClientConfig' with OIDCAuth 'AuthMethod'.
|
||||
Does not use cache, consider using 'cachedOIDCAuth'.
|
||||
@@ -106,7 +115,7 @@ oidcAuth :: DetectAuth
|
||||
oidcAuth AuthInfo{authProvider = Just(AuthProviderConfig "oidc" (Just cfg))} (tls, kubecfg)
|
||||
= Just
|
||||
$ parseOIDCAuthInfo cfg
|
||||
>>= either error (\oidc -> pure (tls, addAuthMethod kubecfg oidc))
|
||||
>>= either (throwM . OIDCAuthParsingException) (\oidc -> pure (tls, addAuthMethod kubecfg oidc))
|
||||
oidcAuth _ _ = Nothing
|
||||
|
||||
-- TODO: Consider doing this whole function atomically, as two threads may miss the cache simultaneously
|
||||
@@ -118,10 +127,11 @@ cachedOIDCAuth :: OIDCCache -> DetectAuth
|
||||
cachedOIDCAuth cache AuthInfo{authProvider = Just(AuthProviderConfig "oidc" (Just cfg))} (tls, kubecfg) = Just $ do
|
||||
m <- readTVarIO cache
|
||||
o <- case findInCache m cfg of
|
||||
Left e -> error e
|
||||
Left e -> throwM $ OIDCAuthParsingException e
|
||||
Right (Just o) -> return o
|
||||
Right Nothing -> do
|
||||
o@(OIDCAuth{..}) <- either error pure =<< parseOIDCAuthInfo cfg
|
||||
o@(OIDCAuth{..}) <- parseOIDCAuthInfo cfg
|
||||
>>= either (throwM . OIDCAuthParsingException) pure
|
||||
let newCache = Map.insert (issuerURL, clientID) o m
|
||||
_ <- atomically $ swapTVar cache newCache
|
||||
return o
|
||||
|
||||
Reference in New Issue
Block a user