Skip to content

Commit c90b1c0

Browse files
committed
First draft: Kube config loader
I needed to move a few methods to TLSUtils due to circular dependencies, this will of course break compatibility with previous versions. I will re-export all the previous functions again. Apart from that, there is a fair bit of code in here without any tests, so next thing I will do is start adding unit tests to make sure the basics are fine. The OIDC and GCP Auth code is difficult to test at unit level, so we may have to figure out some way to integration test those. I noticed that the code has mixed indentation (2 spaces and 4 spaces), all the new code in this commit is 2 space indented. I did not reindent 4 spaces lines for easier code review. We should do that after this work is over. [#2]
1 parent 01b367b commit c90b1c0

File tree

10 files changed

+637
-111
lines changed

10 files changed

+637
-111
lines changed

kubernetes-client/package.yaml

Lines changed: 17 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -13,6 +13,8 @@ license: Apache-2.0
1313
license-file: LICENSE
1414
library:
1515
source-dirs: src
16+
ghc-options:
17+
- -Wall
1618
tests:
1719
spec:
1820
main: Spec.hs
@@ -27,26 +29,41 @@ tests:
2729
dependencies:
2830
- kubernetes-client
2931
extra-source-files:
32+
- README.md
3033
- test/testdata/*
3134
- README.md
3235
dependencies:
3336
- base >=4.7 && <5.0
37+
- base64-bytestring
3438
- bytestring >=0.10.0 && <0.11
3539
- aeson >=1.2.2 && <1.5
40+
- attoparsec >=0.13.0.0 && <0.14
41+
- jsonpath >=0.1.0.0 && <0.2
3642
- connection >=0.2.8
3743
- containers >= 0.6.0.1
3844
- data-default-class >=0.1.2.0
45+
- either
46+
- filepath
47+
- hoauth2
3948
- http-client >=0.5 && <0.7
4049
- http-client-tls >=0.3.5.3
50+
- jwt
4151
- kubernetes-client-core ==0.1.0.1
4252
- microlens >=0.4.3 && <0.5
4353
- mtl >=2.2.1
54+
- oidc-client
4455
- pem >=0.2.4
4556
- safe-exceptions >=0.1.0.0
57+
- stm
4658
- streaming-bytestring >= 0.1.5 && < 0.2.0
4759
- text >=0.11 && <1.3
60+
- time
61+
- timerep
4862
- tls >=1.4.1
63+
- typed-process
64+
- uri-bytestring
4965
- x509 >=1.7.5
5066
- x509-system >=1.6.6
5167
- x509-store >=1.6.7
5268
- x509-validation >=1.6.11
69+
- yaml
Lines changed: 35 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,35 @@
1+
module Kubernetes.Client.Auth.ClientCert where
2+
3+
import Data.Text.Encoding
4+
import Kubernetes.Client.Auth.Internal.Types
5+
import Kubernetes.Client.Internal.TLSUtils
6+
import Kubernetes.Client.KubeConfig
7+
import Kubernetes.OpenAPI (KubernetesClientConfig (..))
8+
import Network.TLS
9+
10+
-- | Detects if kuebconfig file provides 'client-certificate', if it configures TLS client params with the client certificate
11+
clientCertFileAuth :: DetectAuth
12+
clientCertFileAuth auth (tlsParams, cfg) = do
13+
certFile <- clientCertificate auth
14+
keyFile <- clientKey auth
15+
return $ do
16+
cert <- credentialLoadX509 certFile keyFile >>= either error return
17+
let newParams = (setClientCert cert tlsParams)
18+
newCfg = (disableValidateAuthMethods cfg)
19+
return (newParams, newCfg)
20+
21+
-- | Detects if kuebconfig file provides 'client-certificate-data', if it configures TLS client params with the client certificate
22+
clientCertDataAuth :: DetectAuth
23+
clientCertDataAuth auth (tlsParams, cfg) = do
24+
certB64 <- encodeUtf8 <$> clientCertificateData auth
25+
keyB64 <- encodeUtf8 <$> clientKeyData auth
26+
Just $ do
27+
cert <- loadB64EncodedCert certB64 keyB64
28+
let newParams = (setClientCert cert tlsParams)
29+
newCfg = (disableValidateAuthMethods cfg)
30+
return (newParams, newCfg)
31+
32+
-- |Disables the client-side auth methods validation. This is necessary if you are using client cert authentication.
33+
disableValidateAuthMethods :: KubernetesClientConfig -> KubernetesClientConfig
34+
disableValidateAuthMethods kcfg = kcfg { configValidateAuthMethods = False }
35+
Lines changed: 108 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,108 @@
1+
{-# LANGUAGE OverloadedStrings #-}
2+
{-# LANGUAGE RecordWildCards #-}
3+
module Kubernetes.Client.Auth.GCP
4+
( gcpAuth )
5+
where
6+
7+
import Control.Concurrent.STM
8+
import Data.Bifunctor (first)
9+
import Data.Either.Combinators
10+
import Data.Function ((&))
11+
import Data.JSONPath
12+
import Data.Map (Map)
13+
import Data.Text (Text)
14+
import Data.Time.Clock
15+
import Data.Time.LocalTime
16+
import Data.Time.RFC3339
17+
import Kubernetes.Client.Auth.Internal.Types
18+
import Kubernetes.Client.KubeConfig
19+
import Kubernetes.Data.K8sJSONPath
20+
import Kubernetes.OpenAPI.Core
21+
import System.Process.Typed
22+
23+
import qualified Data.Aeson as Aeson
24+
import qualified Data.Map as Map
25+
import qualified Data.Text as Text
26+
import qualified Data.Text.Encoding as Text
27+
import qualified Lens.Micro as L
28+
29+
-- TODO: Add support for scopes based token fetching
30+
data GCPAuth = GCPAuth { gcpAccessToken :: TVar(Maybe Text)
31+
, gcpTokenExpiry :: TVar(Maybe UTCTime)
32+
, gcpCmd :: ProcessConfig () () ()
33+
, gcpTokenKey :: [K8sPathElement]
34+
, gcpExpiryKey :: [K8sPathElement]
35+
}
36+
37+
instance AuthMethod GCPAuth where
38+
applyAuthMethod _ gcp req = do
39+
token <- getToken gcp >>= exceptEither
40+
pure
41+
$ setHeader req [("Authorization", "Bearer " <> (Text.encodeUtf8 token))]
42+
& L.set rAuthTypesL []
43+
44+
-- |Detects if auth-provier name is gcp, if it is configures the 'KubernetesClientConfig' with GCPAuth 'AuthMethod'
45+
gcpAuth :: DetectAuth
46+
gcpAuth AuthInfo{authProvider = Just(AuthProviderConfig "gcp" (Just cfg))} (tls, kubecfg)
47+
= Just $ do
48+
configOfErr <- parseGCPAuthInfo cfg
49+
case configOfErr of
50+
Left e -> error $ Text.unpack e
51+
Right gcp -> pure (tls, addAuthMethod kubecfg gcp)
52+
gcpAuth _ _ = Nothing
53+
54+
exceptEither :: Either Text a -> IO a
55+
exceptEither (Right a) = pure a
56+
exceptEither (Left t) = error (show t)
57+
58+
getToken :: GCPAuth -> IO (Either Text Text)
59+
getToken g@(GCPAuth{..}) = getCurrentToken g
60+
>>= maybe (fetchToken g) (return . Right)
61+
62+
getCurrentToken :: GCPAuth -> IO (Maybe Text)
63+
getCurrentToken (GCPAuth{..}) = do
64+
now <- getCurrentTime
65+
maybeExpiry <- atomically $ readTVar gcpTokenExpiry
66+
maybeToken <- atomically $ readTVar gcpAccessToken
67+
return $ do
68+
expiry <- maybeExpiry
69+
if expiry > now
70+
then maybeToken
71+
else Nothing
72+
73+
-- TODO: log if parsed expiry is invalid
74+
fetchToken :: GCPAuth -> IO (Either Text Text)
75+
fetchToken GCPAuth{..} = do
76+
(stdOut, _) <- readProcess_ gcpCmd
77+
let credsJSON = Aeson.eitherDecode stdOut
78+
& first Text.pack
79+
token = runJSONPath gcpTokenKey =<< credsJSON
80+
expText = runJSONPath gcpExpiryKey =<< credsJSON
81+
expiry :: Either Text (Maybe UTCTime)
82+
expiry = Just <$> (parseExpiryTime =<< expText)
83+
atomically $ writeTVar gcpAccessToken (rightToMaybe token)
84+
atomically $ writeTVar gcpTokenExpiry (either (const Nothing) id expiry)
85+
return token
86+
87+
parseGCPAuthInfo :: Map Text Text -> IO (Either Text GCPAuth)
88+
parseGCPAuthInfo m = do
89+
gcpAccessToken <- atomically $ newTVar $ Map.lookup "access-token" m
90+
case maybe (pure Nothing) ((Just <$>) . parseExpiryTime) $ Map.lookup "expiry" m of
91+
(Left e) -> return $ Left e
92+
Right t -> do
93+
gcpTokenExpiry <- atomically $ newTVar t
94+
return $ do
95+
cmdPath <- Text.unpack <$> lookupEither m "cmd-path"
96+
cmdArgs <- Text.splitOn " " <$> lookupEither m "cmd-args"
97+
let gcpCmd = proc cmdPath (map Text.unpack cmdArgs)
98+
gcpTokenKey = readJSONPath m "token-key" [JSONPath [KeyChild "token_expiry"]]
99+
gcpExpiryKey = readJSONPath m "expiry-key" [JSONPath [KeyChild "access_token"]]
100+
pure $ GCPAuth{..}
101+
102+
lookupEither :: (Show key, Ord key) => Map key val -> key -> Either Text val
103+
lookupEither m k = maybeToRight e $ Map.lookup k m
104+
where e = "Couldn't find key: " <> (Text.pack $ show k) <> " in GCP auth info"
105+
106+
parseExpiryTime :: Text -> Either Text UTCTime
107+
parseExpiryTime s = zonedTimeToUTC <$> parseTimeRFC3339 s
108+
& maybeToRight ("failed to parse token expiry time " <> s)
Lines changed: 9 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,9 @@
1+
module Kubernetes.Client.Auth.Internal.Types where
2+
3+
import Network.TLS as TLS
4+
import Kubernetes.Client.KubeConfig
5+
import Kubernetes.OpenAPI (KubernetesClientConfig)
6+
7+
type DetectAuth = AuthInfo
8+
-> (TLS.ClientParams, KubernetesClientConfig)
9+
-> Maybe (IO (TLS.ClientParams, KubernetesClientConfig))
Lines changed: 168 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,168 @@
1+
{-# LANGUAGE FlexibleContexts #-}
2+
{-# LANGUAGE OverloadedStrings #-}
3+
{-# LANGUAGE RecordWildCards #-}
4+
module Kubernetes.Client.Auth.OIDC
5+
(oidcAuth, OIDCCache, cachedOIDCAuth)
6+
where
7+
8+
import Control.Applicative
9+
import Control.Concurrent.STM
10+
import Data.Either.Combinators
11+
import Data.Function ((&))
12+
import Data.Map (Map)
13+
import Data.Maybe
14+
import Data.Text
15+
import Data.Time.Clock.POSIX (getPOSIXTime)
16+
import Kubernetes.Client.Auth.Internal.Types
17+
import Kubernetes.Client.Internal.TLSUtils
18+
import Kubernetes.Client.KubeConfig
19+
import Kubernetes.OpenAPI.Core
20+
import Network.HTTP.Client
21+
import Network.HTTP.Client.TLS
22+
import Network.OAuth.OAuth2 as OAuth hiding (error)
23+
import Network.TLS as TLS
24+
import URI.ByteString
25+
import Web.JWT as JWT
26+
import Web.OIDC.Client.Discovery as OIDC
27+
28+
import qualified Data.ByteString as BS
29+
import qualified Data.ByteString.Base64 as B64
30+
import qualified Data.Map as Map
31+
import qualified Data.Text as Text
32+
import qualified Data.Text.Encoding as Text
33+
import qualified Lens.Micro as L
34+
35+
data OIDCAuth = OIDCAuth { issuerURL :: Text
36+
, clientID :: Text
37+
, clientSecret :: Text
38+
, tlsParams :: TLS.ClientParams
39+
, idTokenMVar :: TVar(Maybe Text)
40+
, refreshTokenMVar :: TVar(Maybe Text)
41+
}
42+
43+
-- | Cache OIDCAuth based on issuerURL and clientID.
44+
type OIDCCache = TVar (Map (Text, Text) OIDCAuth)
45+
46+
instance AuthMethod OIDCAuth where
47+
applyAuthMethod _ oidc req = do
48+
token <- getToken oidc
49+
pure
50+
$ setHeader req [("Authorization", "Bearer " <> (Text.encodeUtf8 token))]
51+
& L.set rAuthTypesL []
52+
53+
-- TODO: Consider a token expired few seconds before actual expiry to account for time skew
54+
getToken :: OIDCAuth -> IO Text
55+
getToken o@(OIDCAuth{..}) = do
56+
now <- getPOSIXTime
57+
mgr <- newManager tlsManagerSettings
58+
idToken <- atomically $ readTVar idTokenMVar
59+
let maybeExp = idToken
60+
& (>>= decode)
61+
& (fmap claims)
62+
& (>>= JWT.exp)
63+
& (fmap secondsSinceEpoch)
64+
isValidToken = fromMaybe False (fmap (now <) maybeExp)
65+
if not isValidToken
66+
then fetchToken mgr o
67+
else return $ fromMaybe (error "impossible") idToken
68+
69+
fetchToken :: Manager -> OIDCAuth -> IO Text
70+
fetchToken mgr o@(OIDCAuth{..}) = do
71+
maybeToken <- atomically $ readTVar refreshTokenMVar
72+
case maybeToken of
73+
Nothing -> error "cannot refresh id-token without a refresh token"
74+
Just token -> do
75+
tokenEndpoint <- fetchTokenEndpoint mgr o
76+
tokenURI <- exceptEither $ parseURI strictURIParserOptions (Text.encodeUtf8 tokenEndpoint)
77+
let oauth = OAuth2{ oauthClientId = clientID
78+
, oauthClientSecret = clientSecret
79+
, oauthAccessTokenEndpoint = tokenURI
80+
, oauthOAuthorizeEndpoint = tokenURI
81+
, oauthCallback = Nothing
82+
}
83+
oauthToken <- refreshAccessToken mgr oauth (RefreshToken token)
84+
>>= exceptEither
85+
case OAuth.idToken oauthToken of
86+
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."
87+
Just (IdToken t) -> do
88+
_ <- atomically $ writeTVar idTokenMVar (Just t)
89+
return t
90+
91+
fetchTokenEndpoint :: Manager -> OIDCAuth -> IO Text
92+
fetchTokenEndpoint mgr OIDCAuth{..} = do
93+
discover issuerURL mgr
94+
& (fmap configuration)
95+
& (fmap tokenEndpoint)
96+
97+
exceptEither :: Show b => Either b a -> IO a
98+
exceptEither (Right a) = pure a
99+
exceptEither (Left t) = error (show t)
100+
101+
{-
102+
Detects if auth-provier name is oidc, if it is configures the 'KubernetesClientConfig' with OIDCAuth 'AuthMethod'.
103+
Does not use cache, consider using 'cachedOIDCAuth'.
104+
-}
105+
oidcAuth :: DetectAuth
106+
oidcAuth AuthInfo{authProvider = Just(AuthProviderConfig "oidc" (Just cfg))} (tls, kubecfg)
107+
= Just
108+
$ parseOIDCAuthInfo cfg
109+
>>= either error (\oidc -> pure (tls, addAuthMethod kubecfg oidc))
110+
oidcAuth _ _ = Nothing
111+
112+
-- TODO: Consider doing this whole function atomically, as two threads may miss the cache simultaneously
113+
{-
114+
Detects if auth-provier name is oidc, if it is configures the 'KubernetesClientConfig' with OIDCAuth 'AuthMethod'.
115+
First looks for Auth information to be present in 'OIDCCache'. If found returns that, otherwise creates new Auth information and persists it in cache.
116+
-}
117+
cachedOIDCAuth :: OIDCCache -> DetectAuth
118+
cachedOIDCAuth cache AuthInfo{authProvider = Just(AuthProviderConfig "oidc" (Just cfg))} (tls, kubecfg) = Just $ do
119+
m <- atomically $ readTVar cache
120+
o <- case findInCache m cfg of
121+
Left e -> error e
122+
Right (Just o) -> return o
123+
Right Nothing -> do
124+
o@(OIDCAuth{..}) <- either error pure =<< parseOIDCAuthInfo cfg
125+
let newCache = Map.insert (issuerURL, clientID) o m
126+
_ <- atomically $ swapTVar cache newCache
127+
return o
128+
pure (tls, addAuthMethod kubecfg o)
129+
cachedOIDCAuth _ _ _ = Nothing
130+
131+
findInCache :: Map (Text, Text) a -> Map Text Text -> Either String (Maybe a)
132+
findInCache cache cfg = do
133+
issuerURL <- lookupEither cfg "idp-issuer-url"
134+
clientID <- lookupEither cfg "client-id"
135+
return $ Map.lookup (issuerURL, clientID) cache
136+
137+
parseOIDCAuthInfo :: Map Text Text -> IO (Either String OIDCAuth)
138+
parseOIDCAuthInfo m = do
139+
eitherTLSParams <- parseCA m
140+
idTokenMVar <- atomically $ newTVar $ Map.lookup "id-token" m
141+
refreshTokenMVar <- atomically $ newTVar $ Map.lookup "refresh-token" m
142+
return $ do
143+
tlsParams <- eitherTLSParams
144+
issuerURL <- lookupEither m "idp-issuer-url"
145+
clientID <- lookupEither m "client-id"
146+
clientSecret <- lookupEither m "client-secret"
147+
return OIDCAuth{..}
148+
149+
parseCA :: Map Text Text -> IO (Either String TLS.ClientParams)
150+
parseCA m = do
151+
t <- defaultTLSClientParams
152+
fromMaybe (pure $ pure t) (parseCAFile t m <|> parseCAData t m)
153+
154+
parseCAFile :: TLS.ClientParams -> Map Text Text -> Maybe (IO (Either String TLS.ClientParams))
155+
parseCAFile t m = do
156+
caFile <- Text.unpack <$> Map.lookup "idp-certificate-authority" m
157+
return $ updateClientParams t <$> BS.readFile caFile
158+
159+
parseCAData :: TLS.ClientParams -> Map Text Text -> Maybe (IO (Either String TLS.ClientParams))
160+
parseCAData t m = do
161+
caText <- Map.lookup "idp-certificate-authority-data" m
162+
pure . pure
163+
$ (B64.decode $ Text.encodeUtf8 caText)
164+
>>= updateClientParams t
165+
166+
lookupEither :: (Show key, Ord key) => Map key val -> key -> Either String val
167+
lookupEither m k = maybeToRight e $ Map.lookup k m
168+
where e = "Couldn't find key: " <> show k <> " in OIDC auth info"

0 commit comments

Comments
 (0)