Merge pull request #70 from frincon/basic-auth
Implement basic authentication
This commit is contained in:
45
kubernetes-client/src/Kubernetes/Client/Auth/Basic.hs
Normal file
45
kubernetes-client/src/Kubernetes/Client/Auth/Basic.hs
Normal file
@@ -0,0 +1,45 @@
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
{-# LANGUAGE RecordWildCards #-}
|
||||
module Kubernetes.Client.Auth.Basic where
|
||||
|
||||
import Data.ByteString.Base64 ( encode )
|
||||
import Data.Function ( (&) )
|
||||
import Data.Monoid ( (<>) )
|
||||
import Data.Text ( Text )
|
||||
import Kubernetes.Client.Auth.Internal.Types
|
||||
import Kubernetes.OpenAPI.Core
|
||||
import Kubernetes.Client.KubeConfig
|
||||
|
||||
import qualified Data.Text.Encoding as T
|
||||
import qualified Lens.Micro as L
|
||||
|
||||
|
||||
data BasicAuth = BasicAuth { basicAuthUsername :: Text
|
||||
, basicAuthPassword :: Text
|
||||
}
|
||||
|
||||
instance AuthMethod BasicAuth where
|
||||
applyAuthMethod _ BasicAuth{..} req =
|
||||
pure
|
||||
$ req
|
||||
`setHeader` toHeader ("authorization", "Basic " <> encodeBasicAuth)
|
||||
& L.set rAuthTypesL []
|
||||
where
|
||||
encodeBasicAuth = T.decodeUtf8 $ encode $ T.encodeUtf8 $ basicAuthUsername <> ":" <> basicAuthPassword
|
||||
|
||||
-- |Detects if username and password is specified in AuthConfig, if it is configures 'KubernetesClientConfig' with 'BasicAuth'
|
||||
basicAuth :: DetectAuth
|
||||
basicAuth auth (tlsParams, cfg) = do
|
||||
u <- username auth
|
||||
p <- password auth
|
||||
return $ return (tlsParams, setBasicAuth u p cfg)
|
||||
|
||||
-- |Configures the 'KubernetesClientConfig' to use basic authentication.
|
||||
setBasicAuth
|
||||
:: Text -- ^Username
|
||||
-> Text -- ^Password
|
||||
-> KubernetesClientConfig
|
||||
-> KubernetesClientConfig
|
||||
setBasicAuth u p kcfg = kcfg
|
||||
{ configAuthMethods = [AnyAuthMethod (BasicAuth u p)]
|
||||
}
|
||||
@@ -44,6 +44,7 @@ import Data.Maybe
|
||||
import qualified Data.Text as T
|
||||
import qualified Data.Text.Encoding as T
|
||||
import Data.Yaml
|
||||
import Kubernetes.Client.Auth.Basic
|
||||
import Kubernetes.Client.Auth.ClientCert
|
||||
import Kubernetes.Client.Auth.GCP
|
||||
import Kubernetes.Client.Auth.OIDC
|
||||
@@ -172,3 +173,4 @@ applyAuthSettings oidcCache auth input =
|
||||
<|> tokenFileAuth auth input
|
||||
<|> gcpAuth auth input
|
||||
<|> cachedOIDCAuth oidcCache auth input
|
||||
<|> basicAuth auth input
|
||||
|
||||
55
kubernetes-client/test/Kubernetes/Client/Auth/BasicSpec.hs
Normal file
55
kubernetes-client/test/Kubernetes/Client/Auth/BasicSpec.hs
Normal file
@@ -0,0 +1,55 @@
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
module Kubernetes.Client.Auth.BasicSpec where
|
||||
|
||||
import Test.Hspec
|
||||
import Data.Typeable
|
||||
import Data.Maybe ( isJust
|
||||
, isNothing
|
||||
, fromJust
|
||||
)
|
||||
import Kubernetes.Client.Auth.Basic
|
||||
import Kubernetes.Client.KubeConfig
|
||||
import Kubernetes.OpenAPI
|
||||
import Network.TLS ( defaultParamsClient )
|
||||
|
||||
emptyAuthInfo :: AuthInfo
|
||||
emptyAuthInfo = AuthInfo Nothing
|
||||
Nothing
|
||||
Nothing
|
||||
Nothing
|
||||
Nothing
|
||||
Nothing
|
||||
Nothing
|
||||
Nothing
|
||||
Nothing
|
||||
Nothing
|
||||
Nothing
|
||||
Nothing
|
||||
|
||||
spec :: Spec
|
||||
spec = do
|
||||
let testTLSParams = defaultParamsClient "" ""
|
||||
testUsername = Just "testuser"
|
||||
testPassword = Just "testpassword"
|
||||
basicAuthInfo = emptyAuthInfo { username = testUsername, password = testPassword}
|
||||
describe "Basic Authentication" $ do
|
||||
it "should return Nothing if the username an d/or password is not provided" $ do
|
||||
testConfig <- newConfig
|
||||
isNothing (basicAuth emptyAuthInfo (testTLSParams, testConfig))
|
||||
`shouldBe` True
|
||||
isNothing (basicAuth emptyAuthInfo { username = testUsername} (testTLSParams, testConfig))
|
||||
`shouldBe` True
|
||||
isNothing (basicAuth emptyAuthInfo { password = testUsername} (testTLSParams, testConfig))
|
||||
`shouldBe` True
|
||||
|
||||
context "when username and password are provided" $ do
|
||||
it "should return a configuration provider io" $ do
|
||||
testConfig <- newConfig
|
||||
isJust (basicAuth basicAuthInfo (testTLSParams, testConfig)) `shouldBe` True
|
||||
|
||||
it "should configure basic auth" $ do
|
||||
testConfig <- newConfig
|
||||
(_, (KubernetesClientConfig { configAuthMethods = AnyAuthMethod (a) : as })) <-
|
||||
fromJust $ basicAuth basicAuthInfo (testTLSParams, testConfig)
|
||||
null as `shouldBe` True
|
||||
isJust (cast a :: Maybe BasicAuth) `shouldBe` True
|
||||
Reference in New Issue
Block a user