Skip to content

Commit 0886d75

Browse files
committed
add TokenFileAuth which reloads token after expiry
1 parent 95eb28b commit 0886d75

File tree

6 files changed

+235
-86
lines changed

6 files changed

+235
-86
lines changed
Lines changed: 10 additions & 19 deletions
Original file line numberDiff line numberDiff line change
@@ -1,36 +1,27 @@
11
{-# LANGUAGE OverloadedStrings #-}
22
module Kubernetes.Client.Auth.Token where
33

4-
import Data.Monoid ((<>))
5-
import Kubernetes.Client.Auth.Internal.Types
6-
import Kubernetes.Client.KubeConfig (AuthInfo (..))
7-
import Kubernetes.OpenAPI.Core (AnyAuthMethod (..),
8-
KubernetesClientConfig (..))
9-
import Kubernetes.OpenAPI.Model (AuthApiKeyBearerToken (..))
4+
import Data.Monoid ( (<>) )
5+
import Kubernetes.Client.Auth.Internal.Types
6+
import Kubernetes.Client.KubeConfig ( AuthInfo(..) )
7+
import Kubernetes.OpenAPI.Core ( AnyAuthMethod(..)
8+
, KubernetesClientConfig(..)
9+
)
10+
import Kubernetes.OpenAPI.Model ( AuthApiKeyBearerToken(..) )
1011

11-
import qualified Data.Text as T
12-
import qualified Data.Text.IO as T
12+
import qualified Data.Text as T
1313

1414
-- |Detects if token is specified in AuthConfig, if it is configures 'KubernetesClientConfig' with 'AuthApiKeyBearerToken'
1515
tokenAuth :: DetectAuth
1616
tokenAuth auth (tlsParams, cfg) = do
1717
t <- token auth
1818
return $ return (tlsParams, setTokenAuth t cfg)
1919

20-
-- |Detects if token-file is specified in AuthConfig, if it is configures 'KubernetesClientConfig' with 'AuthApiKeyBearerToken'
21-
tokenFileAuth :: DetectAuth
22-
tokenFileAuth auth (tlsParams, cfg) = do
23-
file <- tokenFile auth
24-
return $ do
25-
t <- T.readFile file
26-
return (tlsParams, setTokenAuth t cfg)
27-
2820
-- |Configures the 'KubernetesClientConfig' to use token authentication.
2921
setTokenAuth
3022
:: T.Text -- ^Authentication token
3123
-> KubernetesClientConfig
3224
-> KubernetesClientConfig
3325
setTokenAuth t kcfg = kcfg
34-
{ configAuthMethods = [AnyAuthMethod (AuthApiKeyBearerToken $ "Bearer " <> t)]
35-
}
36-
26+
{ configAuthMethods = [AnyAuthMethod (AuthApiKeyBearerToken $ "Bearer " <> t)]
27+
}
Lines changed: 73 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,73 @@
1+
{-# LANGUAGE OverloadedStrings #-}
2+
{-# LANGUAGE NamedFieldPuns #-}
3+
module Kubernetes.Client.Auth.TokenFile where
4+
5+
import Control.Concurrent.STM
6+
import Data.Function ( (&) )
7+
import Data.Monoid ( (<>) )
8+
import Data.Text ( Text )
9+
import Data.Time.Clock
10+
import Kubernetes.Client.Auth.Internal.Types
11+
import Kubernetes.OpenAPI.Core
12+
import Kubernetes.Client.KubeConfig
13+
hiding ( token )
14+
import qualified Data.Text as T
15+
import qualified Data.Text.IO as T
16+
import qualified Lens.Micro as L
17+
18+
data TokenFileAuth = TokenFileAuth { token :: TVar(Maybe Text)
19+
, expiry :: TVar(Maybe UTCTime)
20+
, file :: FilePath
21+
, period :: NominalDiffTime
22+
}
23+
24+
instance AuthMethod TokenFileAuth where
25+
applyAuthMethod _ tokenFile req = do
26+
t <- getToken tokenFile
27+
pure
28+
$ req
29+
`setHeader` toHeader ("authorization", "Bearer " <> t)
30+
& L.set rAuthTypesL []
31+
32+
-- |Detects if token-file is specified in AuthConfig.
33+
tokenFileAuth :: DetectAuth
34+
tokenFileAuth auth (tlsParams, cfg) = do
35+
file <- tokenFile auth
36+
return $ do
37+
c <- setTokenFileAuth file cfg
38+
return (tlsParams, c)
39+
40+
-- |Configures the 'KubernetesClientConfig' to use TokenFile authentication.
41+
setTokenFileAuth
42+
:: FilePath -> KubernetesClientConfig -> IO KubernetesClientConfig
43+
setTokenFileAuth f kcfg = atomically $ do
44+
t <- newTVar (Nothing :: Maybe Text)
45+
e <- newTVar (Nothing :: Maybe UTCTime)
46+
return kcfg
47+
{ configAuthMethods =
48+
[ AnyAuthMethod
49+
(TokenFileAuth { token = t, expiry = e, file = f, period = 60 })
50+
]
51+
}
52+
53+
getToken :: TokenFileAuth -> IO Text
54+
getToken auth = getCurrentToken auth >>= maybe (reloadToken auth) return
55+
56+
getCurrentToken :: TokenFileAuth -> IO (Maybe Text)
57+
getCurrentToken TokenFileAuth { token, expiry } = do
58+
now <- getCurrentTime
59+
maybeExpiry <- readTVarIO expiry
60+
maybeToken <- readTVarIO token
61+
return $ do
62+
e <- maybeExpiry
63+
if e > now then maybeToken else Nothing
64+
65+
reloadToken :: TokenFileAuth -> IO Text
66+
reloadToken TokenFileAuth { token, expiry, file, period } = do
67+
content <- T.readFile file
68+
let t = T.strip content
69+
now <- getCurrentTime
70+
atomically $ do
71+
writeTVar token (Just t)
72+
writeTVar expiry (Just (addUTCTime period now))
73+
return t

kubernetes-client/src/Kubernetes/Client/Config.hs

Lines changed: 77 additions & 67 deletions
Original file line numberDiff line numberDiff line change
@@ -26,32 +26,36 @@ module Kubernetes.Client.Config
2626
)
2727
where
2828

29-
import qualified Kubernetes.OpenAPI.Core as K
29+
import qualified Kubernetes.OpenAPI.Core as K
3030

31-
import Control.Applicative ((<|>))
32-
import Control.Exception.Safe (MonadThrow, throwM)
33-
import Control.Monad.IO.Class (MonadIO, liftIO)
34-
import qualified Data.ByteString as B
35-
import qualified Data.ByteString.Base64 as B64
36-
import qualified Data.ByteString.Lazy as LazyB
31+
import Control.Applicative ( (<|>) )
32+
import Control.Exception.Safe ( MonadThrow
33+
, throwM
34+
)
35+
import Control.Monad.IO.Class ( MonadIO
36+
, liftIO
37+
)
38+
import qualified Data.ByteString as B
39+
import qualified Data.ByteString.Base64 as B64
40+
import qualified Data.ByteString.Lazy as LazyB
3741
import Data.Either.Combinators
38-
import Data.Function ((&))
42+
import Data.Function ( (&) )
3943
import Data.Maybe
40-
import qualified Data.Text as T
41-
import qualified Data.Text.Encoding as T
42-
import qualified Data.Text.IO as T
44+
import qualified Data.Text as T
45+
import qualified Data.Text.Encoding as T
4346
import Data.Yaml
4447
import Kubernetes.Client.Auth.ClientCert
4548
import Kubernetes.Client.Auth.GCP
4649
import Kubernetes.Client.Auth.OIDC
4750
import Kubernetes.Client.Auth.Token
51+
import Kubernetes.Client.Auth.TokenFile
4852
import Kubernetes.Client.Internal.TLSUtils
4953
import Kubernetes.Client.KubeConfig
50-
import Network.Connection (TLSSettings (..))
51-
import qualified Network.HTTP.Client as NH
52-
import Network.HTTP.Client.TLS (mkManagerSettings)
53-
import qualified Network.TLS as TLS
54-
import System.Environment (getEnv)
54+
import Network.Connection ( TLSSettings(..) )
55+
import qualified Network.HTTP.Client as NH
56+
import Network.HTTP.Client.TLS ( mkManagerSettings )
57+
import qualified Network.TLS as TLS
58+
import System.Environment ( getEnv )
5559
import System.FilePath
5660

5761
data KubeConfigSource = KubeConfigFile FilePath
@@ -64,42 +68,44 @@ data KubeConfigSource = KubeConfigFile FilePath
6468
token is synchronized across all the different clients being used.
6569
-}
6670
mkKubeClientConfig
67-
:: OIDCCache
68-
-> KubeConfigSource
69-
-> IO (NH.Manager, K.KubernetesClientConfig)
71+
:: OIDCCache -> KubeConfigSource -> IO (NH.Manager, K.KubernetesClientConfig)
7072
mkKubeClientConfig oidcCache (KubeConfigFile f) = do
7173
kubeConfig <- decodeFileThrow f
72-
masterURI <- server <$> getCluster kubeConfig
73-
& either (const $ pure "localhost:8080") return
74+
masterURI <-
75+
server
76+
<$> getCluster kubeConfig
77+
& either (const $ pure "localhost:8080") return
7478
tlsParams <- configureTLSParams kubeConfig (takeDirectory f)
7579
clientConfig <- K.newConfig & fmap (setMasterURI masterURI)
76-
(tlsParamsWithAuth, clientConfigWithAuth) <-
77-
case getAuthInfo kubeConfig of
78-
Left _ -> return (tlsParams,clientConfig)
79-
Right (_, auth) -> applyAuthSettings oidcCache auth (tlsParams, clientConfig)
80+
(tlsParamsWithAuth, clientConfigWithAuth) <- case getAuthInfo kubeConfig of
81+
Left _ -> return (tlsParams, clientConfig)
82+
Right (_, auth) ->
83+
applyAuthSettings oidcCache auth (tlsParams, clientConfig)
8084
mgr <- newManager tlsParamsWithAuth
8185
return (mgr, clientConfigWithAuth)
82-
mkKubeClientConfig _ (KubeConfigCluster) = mkInClusterClientConfig
86+
mkKubeClientConfig _ KubeConfigCluster = mkInClusterClientConfig
8387

8488
-- |Creates 'NH.Manager' and 'K.KubernetesClientConfig' assuming it is being executed in a pod
85-
mkInClusterClientConfig :: (MonadIO m, MonadThrow m) => m (NH.Manager, K.KubernetesClientConfig)
89+
mkInClusterClientConfig
90+
:: (MonadIO m, MonadThrow m) => m (NH.Manager, K.KubernetesClientConfig)
8691
mkInClusterClientConfig = do
8792
caStore <- loadPEMCerts $ serviceAccountDir ++ "/ca.crt"
8893
defTlsParams <- liftIO defaultTLSClientParams
89-
mgr <- liftIO . newManager . setCAStore caStore $ disableServerNameValidation defTlsParams
90-
tok <- liftIO . T.readFile $ serviceAccountDir ++ "/token"
94+
mgr <- liftIO . newManager . setCAStore caStore $ disableServerNameValidation
95+
defTlsParams
9196
host <- liftIO $ getEnv "KUBERNETES_SERVICE_HOST"
9297
port <- liftIO $ getEnv "KUBERNETES_SERVICE_PORT"
93-
cfg <- setTokenAuth tok . setMasterURI (T.pack $ "https://" ++ host ++ ":" ++ port) <$> liftIO K.newConfig
98+
cfg <- setMasterURI (T.pack $ "https://" ++ host ++ ":" ++ port) <$> liftIO
99+
(K.newConfig >>= setTokenFileAuth (serviceAccountDir ++ "/token"))
94100
return (mgr, cfg)
95101

96102
-- |Sets the master URI in the 'K.KubernetesClientConfig'.
97103
setMasterURI
98-
:: T.Text -- ^ Master URI
99-
-> K.KubernetesClientConfig
100-
-> K.KubernetesClientConfig
104+
:: T.Text -- ^ Master URI
105+
-> K.KubernetesClientConfig
106+
-> K.KubernetesClientConfig
101107
setMasterURI masterURI kcfg =
102-
kcfg { K.configHost = (LazyB.fromStrict . T.encodeUtf8) masterURI }
108+
kcfg { K.configHost = (LazyB.fromStrict . T.encodeUtf8) masterURI }
103109

104110
-- |Creates a 'NH.Manager' that can handle TLS.
105111
newManager :: TLS.ClientParams -> IO NH.Manager
@@ -110,55 +116,59 @@ serviceAccountDir = "/var/run/secrets/kubernetes.io/serviceaccount"
110116

111117
configureTLSParams :: Config -> FilePath -> IO TLS.ClientParams
112118
configureTLSParams cfg dir = do
113-
defaultTLS <- defaultTLSClientParams
119+
defaultTLS <- defaultTLSClientParams
114120
withCACertData <- addCACertData cfg defaultTLS
115121
withCACertFile <- addCACertFile cfg dir withCACertData
116122
return $ tlsValidation cfg withCACertFile
117123

118124
tlsValidation :: Config -> TLS.ClientParams -> TLS.ClientParams
119-
tlsValidation cfg tlsParams =
120-
case getCluster cfg of
121-
Left _ -> tlsParams
122-
Right c ->
123-
case insecureSkipTLSVerify c of
124-
Just True -> disableServerCertValidation tlsParams
125-
_ -> tlsParams
125+
tlsValidation cfg tlsParams = case getCluster cfg of
126+
Left _ -> tlsParams
127+
Right c -> case insecureSkipTLSVerify c of
128+
Just True -> disableServerCertValidation tlsParams
129+
_ -> tlsParams
126130

127-
addCACertData :: (MonadThrow m) => Config -> TLS.ClientParams -> m TLS.ClientParams
131+
addCACertData
132+
:: (MonadThrow m) => Config -> TLS.ClientParams -> m TLS.ClientParams
128133
addCACertData cfg tlsParams =
129-
let eitherCertText = getCluster cfg
130-
& (>>= (maybeToRight "cert data not provided" . certificateAuthorityData))
131-
in case eitherCertText of
132-
Left _ -> pure tlsParams
133-
Right certBase64 -> do
134-
certText <- B64.decode (T.encodeUtf8 certBase64)
135-
& either (throwM . Base64ParsingFailed) pure
136-
updateClientParams tlsParams certText
137-
& either throwM return
134+
let
135+
eitherCertText =
136+
getCluster cfg
137+
& (>>= (maybeToRight "cert data not provided" . certificateAuthorityData
138+
)
139+
)
140+
in case eitherCertText of
141+
Left _ -> pure tlsParams
142+
Right certBase64 -> do
143+
certText <-
144+
B64.decode (T.encodeUtf8 certBase64)
145+
& either (throwM . Base64ParsingFailed) pure
146+
updateClientParams tlsParams certText & either throwM return
138147

139148
addCACertFile :: Config -> FilePath -> TLS.ClientParams -> IO TLS.ClientParams
140149
addCACertFile cfg dir tlsParams = do
141-
let eitherCertFile = getCluster cfg
142-
>>= maybeToRight "cert file not provided" . certificateAuthority
143-
& fmap T.unpack
144-
& fmap (dir </>)
150+
let eitherCertFile =
151+
getCluster cfg
152+
>>= maybeToRight "cert file not provided"
153+
. certificateAuthority
154+
& fmap T.unpack
155+
& fmap (dir </>)
145156
case eitherCertFile of
146-
Left _ -> return tlsParams
157+
Left _ -> return tlsParams
147158
Right certFile -> do
148159
certText <- B.readFile certFile
149-
return
150-
$ updateClientParams tlsParams certText
151-
& (fromRight tlsParams)
160+
return $ updateClientParams tlsParams certText & fromRight tlsParams
152161

153162
applyAuthSettings
154163
:: OIDCCache
155164
-> AuthInfo
156165
-> (TLS.ClientParams, K.KubernetesClientConfig)
157166
-> IO (TLS.ClientParams, K.KubernetesClientConfig)
158-
applyAuthSettings oidcCache auth input = fromMaybe (pure input)
159-
$ clientCertFileAuth auth input
160-
<|> clientCertDataAuth auth input
161-
<|> tokenAuth auth input
162-
<|> tokenFileAuth auth input
163-
<|> gcpAuth auth input
164-
<|> cachedOIDCAuth oidcCache auth input
167+
applyAuthSettings oidcCache auth input =
168+
fromMaybe (pure input)
169+
$ clientCertFileAuth auth input
170+
<|> clientCertDataAuth auth input
171+
<|> tokenAuth auth input
172+
<|> tokenFileAuth auth input
173+
<|> gcpAuth auth input
174+
<|> cachedOIDCAuth oidcCache auth input

0 commit comments

Comments
 (0)