| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Test.Sandwich.Contexts.Kubernetes.MinikubeCluster
Description
Create and manage Kubernetes clusters via Minikube.
Synopsis
- introduceMinikubeClusterViaNix :: forall context (m :: Type -> Type). (HasBaseContext context, MonadUnliftIO m, HasNixContext context) => MinikubeClusterOptions -> SpecFree (MinikubeClusterContext context) m () -> SpecFree context m ()
- introduceMinikubeClusterViaEnvironment :: forall context (m :: Type -> Type). (HasBaseContext context, MonadUnliftIO m) => MinikubeClusterOptions -> SpecFree (MinikubeClusterContext context) m () -> SpecFree context m ()
- introduceMinikubeCluster' :: forall context (m :: Type -> Type). (HasBaseContext context, MonadUnliftIO m) => FilePath -> MinikubeClusterOptions -> SpecFree (MinikubeClusterContext context) m () -> SpecFree context m ()
- withMinikubeCluster :: (HasBaseContextMonad context m, HasFile context "minikube", MonadLoggerIO m, MonadUnliftIO m, MonadFail m) => MinikubeClusterOptions -> (KubernetesClusterContext -> m a) -> m a
- withMinikubeCluster' :: (HasBaseContextMonad context m, MonadLoggerIO m, MonadUnliftIO m, MonadFail m) => FilePath -> MinikubeClusterOptions -> (KubernetesClusterContext -> m a) -> m a
- withMinikubeCluster'' :: (HasBaseContextMonad context m, MonadLoggerIO m, MonadUnliftIO m, MonadFail m) => String -> FilePath -> MinikubeClusterOptions -> (KubernetesClusterContext -> m a) -> m a
- clusterContainsImageMinikube :: (MonadUnliftIO m, MonadLogger m) => FilePath -> Text -> [Text] -> Text -> m Bool
- getLoadedImagesMinikube :: (MonadUnliftIO m, MonadLogger m) => FilePath -> Text -> [Text] -> m (Set Text)
- loadImageMinikube :: (HasCallStack, MonadUnliftIO m, MonadLoggerIO m, MonadFail m) => FilePath -> Text -> [Text] -> ImageLoadSpec -> m Text
- kubernetesCluster :: Label "kubernetesCluster" KubernetesClusterContext
- data KubernetesClusterContext = KubernetesClusterContext {}
- type HasKubernetesClusterContext context = HasLabel context "kubernetesCluster" KubernetesClusterContext
- data MinikubeClusterOptions = MinikubeClusterOptions {}
- defaultMinikubeClusterOptions :: MinikubeClusterOptions
Introducing a cluster via Minikube
introduceMinikubeClusterViaNix Source #
Arguments
| :: forall context (m :: Type -> Type). (HasBaseContext context, MonadUnliftIO m, HasNixContext context) | |
| => MinikubeClusterOptions | Options |
| -> SpecFree (MinikubeClusterContext context) m () | Child spec |
| -> SpecFree context m () | Parent spec |
Introduce a Minikube cluster, deriving the minikube binary from the Nix context.
introduceMinikubeClusterViaEnvironment Source #
Arguments
| :: forall context (m :: Type -> Type). (HasBaseContext context, MonadUnliftIO m) | |
| => MinikubeClusterOptions | Options |
| -> SpecFree (MinikubeClusterContext context) m () | |
| -> SpecFree context m () |
Introduce a Minikube cluster, deriving the minikube binary from the PATH.
introduceMinikubeCluster' Source #
Arguments
| :: forall context (m :: Type -> Type). (HasBaseContext context, MonadUnliftIO m) | |
| => FilePath | Path to |
| -> MinikubeClusterOptions | |
| -> SpecFree (MinikubeClusterContext context) m () | |
| -> SpecFree context m () |
Introduce a Minikube cluster, passing in the minikube binary path.
Bracket-style functions
Arguments
| :: (HasBaseContextMonad context m, HasFile context "minikube", MonadLoggerIO m, MonadUnliftIO m, MonadFail m) | |
| => MinikubeClusterOptions | Options |
| -> (KubernetesClusterContext -> m a) | |
| -> m a |
Bracket-style variant for introducing a Minikube cluster, using a HasFile context "minikube" constraint.
Arguments
| :: (HasBaseContextMonad context m, MonadLoggerIO m, MonadUnliftIO m, MonadFail m) | |
| => FilePath | Path to |
| -> MinikubeClusterOptions | |
| -> (KubernetesClusterContext -> m a) | |
| -> m a |
Same as withMinikubeCluster, but allows you to pass the path to the minikube binary.
withMinikubeCluster'' Source #
Arguments
| :: (HasBaseContextMonad context m, MonadLoggerIO m, MonadUnliftIO m, MonadFail m) | |
| => String | Cluster name |
| -> FilePath | |
| -> MinikubeClusterOptions | |
| -> (KubernetesClusterContext -> m a) | |
| -> m a |
Same as withMinikubeCluster', but allows you to pass the cluster name.
Image management
These are lower-level and Minikube-specific; prefer working with the functions in Test.Sandwich.Contexts.Kubernetes.Images.
clusterContainsImageMinikube Source #
Arguments
| :: (MonadUnliftIO m, MonadLogger m) | |
| => FilePath | Path to |
| -> Text | Cluster name |
| -> [Text] | Extra flags to pass to |
| -> Text | Image name |
| -> m Bool |
Test if the cluster contains a given image, by cluster name.
getLoadedImagesMinikube Source #
Arguments
| :: (MonadUnliftIO m, MonadLogger m) | |
| => FilePath | Path to |
| -> Text | Cluster name |
| -> [Text] | Extra flags to pass to |
| -> m (Set Text) |
Get the loaded images on a cluster, by cluster name.
Arguments
| :: (HasCallStack, MonadUnliftIO m, MonadLoggerIO m, MonadFail m) | |
| => FilePath | Path to |
| -> Text | Cluster name |
| -> [Text] | Extra flags to pass to |
| -> ImageLoadSpec | Image load spec |
| -> m Text | Returns transformed image name |
Load an image onto a cluster. This image can come from a variety of sources, as specified by the ImageLoadSpec.
Re-exported cluster types
kubernetesCluster :: Label "kubernetesCluster" KubernetesClusterContext Source #
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 # | |
type HasKubernetesClusterContext context = HasLabel context "kubernetesCluster" KubernetesClusterContext Source #
Types
data MinikubeClusterOptions Source #
Constructors
| MinikubeClusterOptions | |