kubernetes-api-client
Example
Load KubeConfig file
import Control.Concurrent.STM (atomically, newTVar)
import Kubernetes.Client (KubeConfigSource (..), mkKubeClientConfig)
import Kubernetes.OpenAPI (Accept (..), MimeJSON (..), dispatchMime)
import qualified Data.Map as Map
import qualified Kubernetes.OpenAPI.API.CoreV1 as CoreV1
main :: IO ()
main = do
oidcCache <- atomically $ newTVar $ Map.fromList []
(mgr, kcfg) <- mkKubeClientConfig oidcCache $ KubeConfigFile "/path/to/kubeconfig"
dispatchMime
mgr
kcfg
(CoreV1.listPodForAllNamespaces (Accept MimeJSON))
>>= print
Load InCluster Config
import Control.Concurrent.STM (atomically, newTVar)
import Data.Function ((&))
import Kubernetes.Client (KubeConfigSource (..), mkKubeClientConfig)
import Kubernetes.OpenAPI (Accept (..), MimeJSON (..), dispatchMime)
import Network.TLS (credentialLoadX509)
import qualified Data.Map as Map
import qualified Kubernetes.OpenAPI.API.CoreV1 as CoreV1
main :: IO ()
main = do
oidcCache <- atomically $ newTVar $ Map.fromList []
(mgr, kcfg) <- mkKubeClientConfig oidcCache KubeConfigCluster
dispatchMime
mgr
kcfg
(CoreV1.listPodForAllNamespaces (Accept MimeJSON))
>>= print
Load config from URL and paths
module Main where
import Data.Function ((&))
import Kubernetes.Client (defaultTLSClientParams,
disableServerCertValidation,
disableServerNameValidation,
disableValidateAuthMethods,
loadPEMCerts, newManager,
setCAStore, setClientCert,
setMasterURI, setTokenAuth)
import Kubernetes.OpenAPI (Accept (..), MimeJSON (..),
dispatchMime, newConfig)
import qualified Kubernetes.OpenAPI.API.CoreV1 as CoreV1
import Network.TLS (credentialLoadX509)
main :: IO ()
main = do
kcfg <-
newConfig
& fmap (setMasterURI "https://mycluster.example.com")
& fmap (setTokenAuth "mytoken")
& fmap disableValidateAuthMethods
myCAStore <- loadPEMCerts "/path/to/ca.crt"
myCert <-
credentialLoadX509 "/path/to/client.crt" "/path/to/client.key"
>>= either error return
tlsParams <-
defaultTLSClientParams
& fmap disableServerNameValidation
& fmap disableServerCertValidation
& fmap (setCAStore myCAStore)
& fmap (setClientCert myCert)
manager <- newManager tlsParams
dispatchMime
manager
kcfg
(CoreV1.listPodForAllNamespaces (Accept MimeJSON))
>>= print
Watch Example
Following is a simple example which
just streams to stdout. First some setup - this assumes kubernetes is accessible
at http://localhost:8001, e.g. after running kubectl proxy
:
> import qualified Data.ByteString.Streaming.Char8 as Q
> manager <- newManager defaultManagerSettings
> defaultConfig <- newConfig
> config = defaultConfig { configHost = "http://localhost:8001", configValidateAuthMethods = False }
> request = listEndpointsForAllNamespaces (Accept MimeJSON)
Launching 'dispatchWatch' with the above we get a stream of endpoints data:
> dispatchWatch manager config request Q.stdout
{"type":\"ADDED\","object":{"kind":\"Endpoints\","apiVersion":"v1","metadata":{"name":"heapster" ....
A more complex example involving some ggprocessing of the stream, the following
prints out the event types of each event. First, define functions to allow us apply
a parser to a stream:
import Data.Aeson
import qualified Data.ByteString.Streaming.Char8 as Q
import Data.JsonStream.Parser
import qualified Streaming.Prelude as S
streamParse ::
FromJSON a =>
Parser a
-> Q.ByteString IO r
-> Stream (Of [a]) IO r
streamParse parser byteStream = do
byteStream & Q.lines & parseEvent parser
parseEvent ::
(FromJSON a, Monad m) =>
Parser a
-> Stream (Q.ByteString m) m r
-> Stream (Of [a]) m r
parseEvent parser byteStream = S.map (parseByteString parser) (S.mapped Q.toStrict byteStream)
Next, define the parser and apply it to the stream:
> eventParser = value :: Parser (WatchEvent V1Endpoints)
> withResponseBody body = streamParse eventParser body & S.map (map eventType)
> dispatchWatch manager config request (S.print . withResponseBody)
[\"ADDED\"]
[\"ADDED\"]
[\"MODIFIED\"]
...
Packages in this example: