| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Test.Sandwich.Contexts.Kubernetes.KindCluster
Description
Create and manage Kubernetes clusters via kind.
Synopsis
- introduceKindClusterViaNix :: forall context (m :: Type -> Type). (HasBaseContext context, MonadUnliftIO m, HasNixContext context) => KindClusterOptions -> SpecFree (KindContext context) m () -> SpecFree context m ()
- introduceKindClusterViaEnvironment :: forall context (m :: Type -> Type). (HasBaseContext context, MonadUnliftIO m) => KindClusterOptions -> SpecFree (KindContext context) m () -> SpecFree context m ()
- introduceKindCluster' :: forall context (m :: Type -> Type). (HasBaseContext context, MonadUnliftIO m) => FilePath -> FilePath -> KindClusterOptions -> SpecFree (KindContext context) m () -> SpecFree context m ()
- withKindCluster :: (MonadLoggerIO m, MonadUnliftIO m, MonadFail m, HasBaseContextMonad context m, HasFile context "kind", HasFile context "kubectl") => KindClusterOptions -> (KubernetesClusterContext -> m a) -> m a
- withKindCluster' :: (MonadLoggerIO m, MonadUnliftIO m, MonadFail m, HasBaseContextMonad context m) => FilePath -> FilePath -> KindClusterOptions -> (KubernetesClusterContext -> m a) -> m a
- clusterContainsImageKind :: (HasCallStack, MonadUnliftIO m, MonadLogger m) => KubernetesClusterContext -> Text -> FilePath -> Maybe [(String, String)] -> Text -> m Bool
- getLoadedImagesKind :: (HasCallStack, MonadUnliftIO m, MonadLogger m) => KubernetesClusterContext -> Text -> FilePath -> Maybe [(String, String)] -> m (Set Text)
- loadImageKind :: (HasCallStack, MonadUnliftIO m, MonadLoggerIO m) => FilePath -> Text -> ImageLoadSpec -> Maybe [(String, String)] -> m Text
- data KubernetesClusterContext = KubernetesClusterContext {}
- kubernetesCluster :: Label "kubernetesCluster" KubernetesClusterContext
- type HasKubernetesClusterContext context = HasLabel context "kubernetesCluster" KubernetesClusterContext
- data KindClusterOptions = KindClusterOptions {}
- defaultKindClusterOptions :: KindClusterOptions
- data KindClusterName
- data ExtraPortMapping = ExtraPortMapping {}
- data ExtraMount = ExtraMount {}
- type KindContext context = LabelValue "kubernetesCluster" KubernetesClusterContext :> (LabelValue "file-kubectl" (EnvironmentFile "kubectl") :> (LabelValue "file-kind" (EnvironmentFile "kind") :> context))
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
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'.
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 |
| -> Maybe [(String, String)] | Extra environment variables |
| -> Text | |
| -> m Bool |
Test if the Kind cluster contains a given image.
Arguments
| :: (HasCallStack, MonadUnliftIO m, MonadLogger m) | |
| => KubernetesClusterContext | |
| -> Text | Driver (should be "docker" or "podman") |
| -> FilePath | Path to |
| -> Maybe [(String, String)] | Extra environment variables |
| -> m (Set Text) |
Get the set of loaded images on the given Kind cluster.
Arguments
| :: (HasCallStack, MonadUnliftIO m, MonadLoggerIO m) | |
| => FilePath | Path to |
| -> 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
data KubernetesClusterContext Source #
Constructors
| KubernetesClusterContext | |
Instances
| Show KubernetesClusterContext Source # | |
Defined in Test.Sandwich.Contexts.Kubernetes.Types Methods showsPrec :: Int -> KubernetesClusterContext -> ShowS # show :: KubernetesClusterContext -> String # showList :: [KubernetesClusterContext] -> ShowS # | |
kubernetesCluster :: Label "kubernetesCluster" KubernetesClusterContext Source #
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 |
Instances
| Show KindClusterName Source # | |
Defined in Test.Sandwich.Contexts.Kubernetes.KindCluster Methods showsPrec :: Int -> KindClusterName -> ShowS # show :: KindClusterName -> String # showList :: [KindClusterName] -> ShowS # | |
| Eq KindClusterName Source # | |
Defined in Test.Sandwich.Contexts.Kubernetes.KindCluster Methods (==) :: KindClusterName -> KindClusterName -> Bool # (/=) :: KindClusterName -> KindClusterName -> Bool # | |
data ExtraPortMapping Source #
Constructors
| ExtraPortMapping | |
Fields
| |
Instances
| ToJSON ExtraPortMapping Source # | |
Defined in Test.Sandwich.Contexts.Kubernetes.KindCluster.Config Methods toJSON :: ExtraPortMapping -> Value # toEncoding :: ExtraPortMapping -> Encoding # toJSONList :: [ExtraPortMapping] -> Value # toEncodingList :: [ExtraPortMapping] -> Encoding # omitField :: ExtraPortMapping -> Bool # | |
data ExtraMount Source #
Constructors
| ExtraMount | |
Fields
| |
Instances
| ToJSON ExtraMount Source # | |
Defined in Test.Sandwich.Contexts.Kubernetes.KindCluster.Config Methods toJSON :: ExtraMount -> Value # toEncoding :: ExtraMount -> Encoding # toJSONList :: [ExtraMount] -> Value # toEncodingList :: [ExtraMount] -> Encoding # omitField :: ExtraMount -> Bool # | |
type KindContext context = LabelValue "kubernetesCluster" KubernetesClusterContext :> (LabelValue "file-kubectl" (EnvironmentFile "kubectl") :> (LabelValue "file-kind" (EnvironmentFile "kind") :> context)) Source #
Alias to make type signatures shorter.