Safe Haskell | None |
---|---|
Language | Haskell2010 |
Test.Sandwich.Contexts.Kubernetes
Description
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 ()
- defaultKindClusterOptions :: KindClusterOptions
- data KindClusterOptions = KindClusterOptions {}
- 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 ()
- defaultMinikubeClusterOptions :: MinikubeClusterOptions
- data MinikubeClusterOptions = MinikubeClusterOptions {}
- waitForPodsToExist :: (MonadUnliftIO m, MonadLogger m, MonadReader context m, HasKubernetesClusterContext context) => Text -> Map Text Text -> Double -> Maybe Int -> m ()
- waitForPodsToBeReady :: (MonadUnliftIO m, MonadLogger m, MonadReader context m, HasKubernetesClusterContext context, HasFile context "kubectl") => Text -> Map Text Text -> Double -> m ()
- waitForServiceEndpointsToExist :: (MonadUnliftIO m, MonadLogger m, MonadReader context m, HasKubernetesClusterContext context) => Text -> Text -> Double -> m ()
- askKubectlArgs :: KubectlBasic context m => m (FilePath, [(String, String)])
- askKubectlEnvironment :: KubernetesClusterBasic context m => m [(String, String)]
- getKubectlEnvironment :: MonadLoggerIO m => KubernetesClusterContext -> m [(String, String)]
- withForwardKubernetesService :: KubectlBasic context m => Text -> Text -> (URI -> m a) -> m a
- withForwardKubernetesService' :: (MonadLoggerIO m, MonadUnliftIO m, HasBaseContextMonad context m) => KubernetesClusterContext -> FilePath -> Text -> Text -> (URI -> m a) -> m a
- withKubectlLogs :: (MonadLogger m, MonadFail m, MonadUnliftIO m, HasBaseContextMonad ctx m, HasFile ctx "kubectl") => FilePath -> Text -> Text -> Maybe Text -> Bool -> (KubectlLogsContext -> m a) -> m a
- data KubectlLogsContext = KubectlLogsContext {}
- withKubectlPortForward :: (HasCallStack, KubectlBasic context m) => FilePath -> Text -> Text -> PortNumber -> (KubectlPortForwardContext -> m a) -> m a
- withKubectlPortForward' :: (HasCallStack, KubernetesBasic context m) => FilePath -> FilePath -> Text -> (PortNumber -> Bool) -> Maybe PortNumber -> Text -> PortNumber -> (KubectlPortForwardContext -> m a) -> m a
- newtype KubectlPortForwardContext = KubectlPortForwardContext {}
- kubernetesCluster :: Label "kubernetesCluster" KubernetesClusterContext
- data KubernetesClusterContext = KubernetesClusterContext {}
- data KubernetesClusterType
- = KubernetesClusterKind { }
- | KubernetesClusterMinikube { }
- type HasKubernetesClusterContext context = HasLabel context "kubernetesCluster" KubernetesClusterContext
- type KubernetesBasic context (m :: Type -> Type) = (MonadLoggerIO m, MonadUnliftIO m, HasBaseContextMonad context m)
- type KubernetesClusterBasic context (m :: Type -> Type) = (KubernetesBasic context m, HasKubernetesClusterContext context)
- type KubectlBasic context (m :: Type -> Type) = (KubernetesClusterBasic context m, HasFile context "kubectl")
- type NixContextBasic context (m :: Type -> Type) = (MonadLoggerIO m, MonadUnliftIO m, HasBaseContextMonad context m, HasNixContext context)
- type KubernetesBasicWithoutReader context (m :: Type -> Type) = (MonadLoggerIO m, MonadUnliftIO m, HasBaseContext context)
- type KubernetesClusterBasicWithoutReader context (m :: Type -> Type) = (MonadUnliftIO m, HasBaseContext context, HasKubernetesClusterContext context)
- type KubectlBasicWithoutReader context (m :: Type -> Type) = (MonadUnliftIO m, HasBaseContext context, HasKubernetesClusterContext context, HasFile context "kubectl")
Kind clusters
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.
data KindClusterOptions Source #
Constructors
KindClusterOptions | |
Fields
|
Minikube clusters
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.
data MinikubeClusterOptions Source #
Constructors
MinikubeClusterOptions | |
Wait for pods/services
Arguments
:: (MonadUnliftIO m, MonadLogger m, MonadReader context m, HasKubernetesClusterContext context) | |
=> Text | Namespace |
-> Map Text Text | Pod labels |
-> Double | Time in seconds to wait |
-> Maybe Int | Optional desired pod count to wait for |
-> m () |
Wait for a set of pods to exist, specified by a set of labels.
Arguments
:: (MonadUnliftIO m, MonadLogger m, MonadReader context m, HasKubernetesClusterContext context, HasFile context "kubectl") | |
=> Text | Namespace |
-> Map Text Text | Pod labels |
-> Double | Time in seconds to wait |
-> m () |
Wait for a set of pods to be in the Ready condition, specified by a set of labels.
waitForServiceEndpointsToExist Source #
Arguments
:: (MonadUnliftIO m, MonadLogger m, MonadReader context m, HasKubernetesClusterContext context) | |
=> Text | Namespace |
-> Text | Service name |
-> Double | Time in seconds to wait |
-> m () |
Wait for a service to have its set of endpoints ready, i.e.:
- They each have at least one IP address
- They each have an empty set of "not ready addresses"
Run commands with kubectl
Arguments
:: KubectlBasic context m | |
=> m (FilePath, [(String, String)]) | Returns the |
Retrieve the kubectl
binary path and the set of environment variables to use when invoking it.
Derives these from a HasFile
context and the KubernetesClusterContext
respectively.
Useful for running Kubectl commands with createProcess
etc.
askKubectlEnvironment Source #
Arguments
:: KubernetesClusterBasic context m | |
=> m [(String, String)] | Returns the |
Same as askKubectlArgs
, but only returns the environment variables.
getKubectlEnvironment Source #
Arguments
:: MonadLoggerIO m | |
=> KubernetesClusterContext | Kubernetes cluster context |
-> m [(String, String)] | Returns the |
Same as askKubectlArgs
, but only returns the environment variables.
Forward services
withForwardKubernetesService Source #
Arguments
:: KubectlBasic context m | |
=> Text | Namespace |
-> Text | Service name |
-> (URI -> m a) | Callback receiving the service |
-> m a |
Forward a Kubernetes service, so that it can be reached at a local URI.
withForwardKubernetesService' Source #
Arguments
:: (MonadLoggerIO m, MonadUnliftIO m, HasBaseContextMonad context m) | |
=> KubernetesClusterContext | Kubernetes cluster context |
-> FilePath | Binary path for kubectl |
-> Text | Namespace |
-> Text | Service name |
-> (URI -> m a) | Callback receiving the service |
-> m a |
Same as withForwardKubernetesService
, but allows you to pass in the KubernetesClusterContext
and kubectl
binary.
Logs
Arguments
:: (MonadLogger m, MonadFail m, MonadUnliftIO m, HasBaseContextMonad ctx m, HasFile ctx "kubectl") | |
=> FilePath | Kubeconfig file |
-> Text | Namespace |
-> Text | Log target (pod, service, etc.) |
-> Maybe Text | Specific container to get logs from |
-> Bool | Whether to interrupt the process to shut it down while cleaning up |
-> (KubectlLogsContext -> m a) | Callback receiving the |
-> m a |
Run a kubectl logs
process, placing the logs in a file in the current test node directory.
Note that this will stop working if the pod you're talking to goes away (even if you do it against a service). If this happens, a rerun of the command is needed to resume log forwarding.
data KubectlLogsContext Source #
Constructors
KubectlLogsContext | |
Fields |
Port forwarding
withKubectlPortForward Source #
Arguments
:: (HasCallStack, KubectlBasic context m) | |
=> FilePath | Path to kubeconfig file |
-> Text | Namespace |
-> Text | Target name (pod, service, etc.) |
-> PortNumber | Target port number |
-> (KubectlPortForwardContext -> m a) | |
-> m a |
Run a kubectl port-forward
process, making the port available in the KubectlPortForwardContext
.
Note that this will stop working if the pod you're talking to goes away (even if you do it against a service). If this happens, a rerun of the command is needed to resume port forwarding.
withKubectlPortForward' Source #
Arguments
:: (HasCallStack, KubernetesBasic context m) | |
=> FilePath | |
-> FilePath | Path to kubeconfig file |
-> Text | Namespace |
-> (PortNumber -> Bool) | Callback to check if the proposed local port is acceptable |
-> Maybe PortNumber | |
-> Text | Target name (pod, service, etc.) |
-> PortNumber | Target port number |
-> (KubectlPortForwardContext -> m a) | |
-> m a |
Same as withKubectlPortForward
, but allows you to pass in the kubectl
binary path.
newtype KubectlPortForwardContext Source #
Constructors
KubectlPortForwardContext | |
Fields |
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 # |
data KubernetesClusterType Source #
Constructors
KubernetesClusterKind | |
KubernetesClusterMinikube | |
Instances
Show KubernetesClusterType Source # | |
Defined in Test.Sandwich.Contexts.Kubernetes.Types Methods showsPrec :: Int -> KubernetesClusterType -> ShowS # show :: KubernetesClusterType -> String # showList :: [KubernetesClusterType] -> ShowS # | |
Eq KubernetesClusterType Source # | |
Defined in Test.Sandwich.Contexts.Kubernetes.Types Methods (==) :: KubernetesClusterType -> KubernetesClusterType -> Bool # (/=) :: KubernetesClusterType -> KubernetesClusterType -> Bool # |
type HasKubernetesClusterContext context = HasLabel context "kubernetesCluster" KubernetesClusterContext Source #
Constraint aliases
type KubernetesBasic context (m :: Type -> Type) = (MonadLoggerIO m, MonadUnliftIO m, HasBaseContextMonad context m) Source #
type KubernetesClusterBasic context (m :: Type -> Type) = (KubernetesBasic context m, HasKubernetesClusterContext context) Source #
type KubectlBasic context (m :: Type -> Type) = (KubernetesClusterBasic context m, HasFile context "kubectl") Source #
type NixContextBasic context (m :: Type -> Type) = (MonadLoggerIO m, MonadUnliftIO m, HasBaseContextMonad context m, HasNixContext context) Source #
type KubernetesBasicWithoutReader context (m :: Type -> Type) = (MonadLoggerIO m, MonadUnliftIO m, HasBaseContext context) Source #
type KubernetesClusterBasicWithoutReader context (m :: Type -> Type) = (MonadUnliftIO m, HasBaseContext context, HasKubernetesClusterContext context) Source #
type KubectlBasicWithoutReader context (m :: Type -> Type) = (MonadUnliftIO m, HasBaseContext context, HasKubernetesClusterContext context, HasFile context "kubectl") Source #