sandwich-contexts-kubernetes
Safe HaskellNone
LanguageHaskell2010

Test.Sandwich.Contexts.Kubernetes.KindCluster

Description

Create and manage Kubernetes clusters via kind.

Synopsis

Documentation

introduceKindClusterViaNix Source #

Arguments

:: forall context (m :: Type -> Type). (HasBaseContext context, MonadUnliftIO m, HasNixContext context) 
=> KindClusterOptions

Options

-> SpecFree (KindContext context) m ()

Child spec

-> SpecFree context m ()

Parent spec

Introduce a Kubernetes cluster using kind, deriving the kind and kubectl binaries from the Nix context.

introduceKindClusterViaEnvironment Source #

Arguments

:: forall context (m :: Type -> Type). (HasBaseContext context, MonadUnliftIO m) 
=> KindClusterOptions

Options

-> SpecFree (KindContext context) m () 
-> SpecFree context m () 

Introduce a Kubernetes cluster using kind, deriving the kind and kubectl binaries from the PATH.

introduceKindCluster' Source #

Arguments

:: forall context (m :: Type -> Type). (HasBaseContext context, MonadUnliftIO m) 
=> FilePath

Path to kind binary

-> FilePath

Path to kubectl binary

-> KindClusterOptions 
-> SpecFree (KindContext context) m () 
-> SpecFree context m () 

Introduce a Kubernetes cluster using kind, passing in the kind and kubectl binaries.

Bracket-style versions

withKindCluster Source #

Arguments

:: (MonadLoggerIO m, MonadUnliftIO m, MonadFail m, HasBaseContextMonad context m, HasFile context "kind", HasFile context "kubectl") 
=> KindClusterOptions

Options

-> (KubernetesClusterContext -> m a) 
-> m a 

Bracket-style variant of introduceKindCluster'.

withKindCluster' Source #

Arguments

:: (MonadLoggerIO m, MonadUnliftIO m, MonadFail m, HasBaseContextMonad context m) 
=> FilePath

Path to the kind binary

-> FilePath

Path to the kubectl binary

-> KindClusterOptions 
-> (KubernetesClusterContext -> m a) 
-> m a 

Same as withKindCluster, but allows you to pass in the paths to the kind and kubectl binaries.

Image management

These are lower-level and Kind-specific; prefer working with the functions in Test.Sandwich.Contexts.Kubernetes.Images.

clusterContainsImageKind Source #

Arguments

:: (HasCallStack, MonadUnliftIO m, MonadLogger m) 
=> KubernetesClusterContext 
-> Text

Driver (should be "docker" or "podman")

-> FilePath

Path to kind binary

-> Maybe [(String, String)]

Extra environment variables

-> Text 
-> m Bool 

Test if the Kind cluster contains a given image.

getLoadedImagesKind Source #

Arguments

:: (HasCallStack, MonadUnliftIO m, MonadLogger m) 
=> KubernetesClusterContext 
-> Text

Driver (should be "docker" or "podman")

-> FilePath

Path to kind binary

-> Maybe [(String, String)]

Extra environment variables

-> m (Set Text) 

Get the set of loaded images on the given Kind cluster.

loadImageKind Source #

Arguments

:: (HasCallStack, MonadUnliftIO m, MonadLoggerIO m) 
=> FilePath

Path to kind binary

-> Text

Cluster name

-> ImageLoadSpec

Image load spec

-> Maybe [(String, String)]

Extra environment variables

-> m Text

Returns transformed image name

Load an image into a Kind cluster.

Re-exported types

type HasKubernetesClusterContext context = HasLabel context "kubernetesCluster" KubernetesClusterContext Source #

Types

data KindClusterOptions Source #

Constructors

KindClusterOptions 

Fields

data KindClusterName Source #

Constructors

KindClusterNameExactly Text

Give the kind cluster an exact name

KindClusterNameAutogenerate (Maybe Text)

Autogenerate the cluster name, with an optional fixed prefix

data ExtraPortMapping Source #

Constructors

ExtraPortMapping 

Fields

data ExtraMount Source #

Constructors

ExtraMount 

Fields

type KindContext context = LabelValue "kubernetesCluster" KubernetesClusterContext :> (LabelValue "file-kubectl" (EnvironmentFile "kubectl") :> (LabelValue "file-kind" (EnvironmentFile "kind") :> context)) Source #

Alias to make type signatures shorter.