kubernetes-api-client-0.6.0.0: Client library for Kubernetes
Safe HaskellSafe-Inferred
LanguageHaskell2010

Kubernetes.Client.KubeConfig

Description

This module contains the definition of the data model of the kubeconfig.

The official definition of the kubeconfig is defined in https://github.com/kubernetes/client-go/blob/master/tools/clientcmd/api/v1/types.go.

This is a mostly straightforward translation into Haskell, with FromJSON and ToJSON instances defined.

Synopsis

Documentation

data Config Source #

Represents a kubeconfig.

Instances

Instances details
FromJSON Config Source # 
Instance details

Defined in Kubernetes.Client.KubeConfig

ToJSON Config Source # 
Instance details

Defined in Kubernetes.Client.KubeConfig

Generic Config Source # 
Instance details

Defined in Kubernetes.Client.KubeConfig

Associated Types

type Rep Config :: Type -> Type #

Methods

from :: Config -> Rep Config x #

to :: Rep Config x -> Config #

Show Config Source # 
Instance details

Defined in Kubernetes.Client.KubeConfig

Eq Config Source # 
Instance details

Defined in Kubernetes.Client.KubeConfig

Methods

(==) :: Config -> Config -> Bool #

(/=) :: Config -> Config -> Bool #

type Rep Config Source # 
Instance details

Defined in Kubernetes.Client.KubeConfig

newtype Preferences Source #

Constructors

Preferences 

Fields

Instances

Instances details
FromJSON Preferences Source # 
Instance details

Defined in Kubernetes.Client.KubeConfig

ToJSON Preferences Source # 
Instance details

Defined in Kubernetes.Client.KubeConfig

Generic Preferences Source # 
Instance details

Defined in Kubernetes.Client.KubeConfig

Associated Types

type Rep Preferences :: Type -> Type #

Show Preferences Source # 
Instance details

Defined in Kubernetes.Client.KubeConfig

Eq Preferences Source # 
Instance details

Defined in Kubernetes.Client.KubeConfig

type Rep Preferences Source # 
Instance details

Defined in Kubernetes.Client.KubeConfig

type Rep Preferences = D1 ('MetaData "Preferences" "Kubernetes.Client.KubeConfig" "kubernetes-api-client-0.6.0.0-1KRDTGbyOFK6dGLoEKPZYD" 'True) (C1 ('MetaCons "Preferences" 'PrefixI 'True) (S1 ('MetaSel ('Just "colors") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool))))

data Cluster Source #

Instances

Instances details
FromJSON Cluster Source # 
Instance details

Defined in Kubernetes.Client.KubeConfig

ToJSON Cluster Source # 
Instance details

Defined in Kubernetes.Client.KubeConfig

Generic Cluster Source # 
Instance details

Defined in Kubernetes.Client.KubeConfig

Associated Types

type Rep Cluster :: Type -> Type #

Methods

from :: Cluster -> Rep Cluster x #

to :: Rep Cluster x -> Cluster #

Show Cluster Source # 
Instance details

Defined in Kubernetes.Client.KubeConfig

Eq Cluster Source # 
Instance details

Defined in Kubernetes.Client.KubeConfig

Methods

(==) :: Cluster -> Cluster -> Bool #

(/=) :: Cluster -> Cluster -> Bool #

type Rep Cluster Source # 
Instance details

Defined in Kubernetes.Client.KubeConfig

type Rep Cluster = D1 ('MetaData "Cluster" "Kubernetes.Client.KubeConfig" "kubernetes-api-client-0.6.0.0-1KRDTGbyOFK6dGLoEKPZYD" 'False) (C1 ('MetaCons "Cluster" 'PrefixI 'True) ((S1 ('MetaSel ('Just "server") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "insecureSkipTLSVerify") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool))) :*: (S1 ('MetaSel ('Just "certificateAuthority") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "certificateAuthorityData") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)))))

data NamedEntity a (typeKey :: Symbol) Source #

Constructors

NamedEntity 

Fields

Instances

Instances details
(FromJSON a, Typeable a, KnownSymbol s) => FromJSON (NamedEntity a s) Source # 
Instance details

Defined in Kubernetes.Client.KubeConfig

(ToJSON a, KnownSymbol s) => ToJSON (NamedEntity a s) Source # 
Instance details

Defined in Kubernetes.Client.KubeConfig

Generic (NamedEntity a typeKey) Source # 
Instance details

Defined in Kubernetes.Client.KubeConfig

Associated Types

type Rep (NamedEntity a typeKey) :: Type -> Type #

Methods

from :: NamedEntity a typeKey -> Rep (NamedEntity a typeKey) x #

to :: Rep (NamedEntity a typeKey) x -> NamedEntity a typeKey #

Show a => Show (NamedEntity a typeKey) Source # 
Instance details

Defined in Kubernetes.Client.KubeConfig

Methods

showsPrec :: Int -> NamedEntity a typeKey -> ShowS #

show :: NamedEntity a typeKey -> String #

showList :: [NamedEntity a typeKey] -> ShowS #

Eq a => Eq (NamedEntity a typeKey) Source # 
Instance details

Defined in Kubernetes.Client.KubeConfig

Methods

(==) :: NamedEntity a typeKey -> NamedEntity a typeKey -> Bool #

(/=) :: NamedEntity a typeKey -> NamedEntity a typeKey -> Bool #

type Rep (NamedEntity a typeKey) Source # 
Instance details

Defined in Kubernetes.Client.KubeConfig

type Rep (NamedEntity a typeKey) = D1 ('MetaData "NamedEntity" "Kubernetes.Client.KubeConfig" "kubernetes-api-client-0.6.0.0-1KRDTGbyOFK6dGLoEKPZYD" 'False) (C1 ('MetaCons "NamedEntity" 'PrefixI 'True) (S1 ('MetaSel ('Just "name") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "entity") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))

data AuthInfo Source #

Instances

Instances details
FromJSON AuthInfo Source # 
Instance details

Defined in Kubernetes.Client.KubeConfig

ToJSON AuthInfo Source # 
Instance details

Defined in Kubernetes.Client.KubeConfig

Generic AuthInfo Source # 
Instance details

Defined in Kubernetes.Client.KubeConfig

Associated Types

type Rep AuthInfo :: Type -> Type #

Methods

from :: AuthInfo -> Rep AuthInfo x #

to :: Rep AuthInfo x -> AuthInfo #

Show AuthInfo Source # 
Instance details

Defined in Kubernetes.Client.KubeConfig

Eq AuthInfo Source # 
Instance details

Defined in Kubernetes.Client.KubeConfig

type Rep AuthInfo Source # 
Instance details

Defined in Kubernetes.Client.KubeConfig

type Rep AuthInfo = D1 ('MetaData "AuthInfo" "Kubernetes.Client.KubeConfig" "kubernetes-api-client-0.6.0.0-1KRDTGbyOFK6dGLoEKPZYD" 'False) (C1 ('MetaCons "AuthInfo" 'PrefixI 'True) (((S1 ('MetaSel ('Just "clientCertificate") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe FilePath)) :*: (S1 ('MetaSel ('Just "clientCertificateData") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "clientKey") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe FilePath)))) :*: (S1 ('MetaSel ('Just "clientKeyData") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)) :*: (S1 ('MetaSel ('Just "token") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "tokenFile") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe FilePath))))) :*: ((S1 ('MetaSel ('Just "impersonate") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)) :*: (S1 ('MetaSel ('Just "impersonateGroups") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [Text])) :*: S1 ('MetaSel ('Just "impersonateUserExtra") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Map Text [Text]))))) :*: (S1 ('MetaSel ('Just "username") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)) :*: (S1 ('MetaSel ('Just "password") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "authProvider") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe AuthProviderConfig)))))))

data Context Source #

Constructors

Context 

Instances

Instances details
FromJSON Context Source # 
Instance details

Defined in Kubernetes.Client.KubeConfig

ToJSON Context Source # 
Instance details

Defined in Kubernetes.Client.KubeConfig

Generic Context Source # 
Instance details

Defined in Kubernetes.Client.KubeConfig

Associated Types

type Rep Context :: Type -> Type #

Methods

from :: Context -> Rep Context x #

to :: Rep Context x -> Context #

Show Context Source # 
Instance details

Defined in Kubernetes.Client.KubeConfig

Eq Context Source # 
Instance details

Defined in Kubernetes.Client.KubeConfig

Methods

(==) :: Context -> Context -> Bool #

(/=) :: Context -> Context -> Bool #

type Rep Context Source # 
Instance details

Defined in Kubernetes.Client.KubeConfig

type Rep Context = D1 ('MetaData "Context" "Kubernetes.Client.KubeConfig" "kubernetes-api-client-0.6.0.0-1KRDTGbyOFK6dGLoEKPZYD" 'False) (C1 ('MetaCons "Context" 'PrefixI 'True) (S1 ('MetaSel ('Just "cluster") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: (S1 ('MetaSel ('Just "authInfo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "namespace") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)))))

data AuthProviderConfig Source #

Constructors

AuthProviderConfig 

Fields

Instances

Instances details
FromJSON AuthProviderConfig Source # 
Instance details

Defined in Kubernetes.Client.KubeConfig

ToJSON AuthProviderConfig Source # 
Instance details

Defined in Kubernetes.Client.KubeConfig

Generic AuthProviderConfig Source # 
Instance details

Defined in Kubernetes.Client.KubeConfig

Associated Types

type Rep AuthProviderConfig :: Type -> Type #

Show AuthProviderConfig Source # 
Instance details

Defined in Kubernetes.Client.KubeConfig

Eq AuthProviderConfig Source # 
Instance details

Defined in Kubernetes.Client.KubeConfig

type Rep AuthProviderConfig Source # 
Instance details

Defined in Kubernetes.Client.KubeConfig

type Rep AuthProviderConfig = D1 ('MetaData "AuthProviderConfig" "Kubernetes.Client.KubeConfig" "kubernetes-api-client-0.6.0.0-1KRDTGbyOFK6dGLoEKPZYD" 'False) (C1 ('MetaCons "AuthProviderConfig" 'PrefixI 'True) (S1 ('MetaSel ('Just "name") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "config") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Map Text Text)))))

getContext :: Config -> Either String Context Source #

Returns the currently active context.

getAuthInfo :: Config -> Either String (Text, AuthInfo) Source #

Returns the currently active user.

getCluster :: Config -> Either String Cluster Source #

Returns the currently active cluster.