Safe Haskell | None |
---|---|
Language | Haskell2010 |
Test.Sandwich.Contexts.Kubernetes.MinioS3Server
Description
Install MinIO S3 servers onto a Kubernetes cluster.
Such a server is provided as a generic TestS3Server
, so that you can easily run the same tests against both Kubernetes environments and normal ones. See for example the sandwich-contexts-minio
package.
Synopsis
- introduceK8SMinioS3Server :: forall context (m :: Type -> Type). (Typeable context, KubectlBasicWithoutReader context m, HasMinioOperatorContext context) => MinioS3ServerOptions -> SpecFree (LabelValue "testS3Server" TestS3Server :> context) m () -> SpecFree context m ()
- introduceK8SMinioS3Server' :: forall context (m :: Type -> Type). (Typeable context, KubectlBasic context m, HasMinioOperatorContext context) => KubernetesClusterContext -> MinioS3ServerOptions -> SpecFree (LabelValue "testS3Server" TestS3Server :> context) m () -> SpecFree context m ()
- withK8SMinioS3Server :: (Typeable context, MonadFail m, KubernetesBasic context m, HasFile context "kubectl") => KubernetesClusterContext -> MinioOperatorContext -> MinioS3ServerOptions -> (TestS3Server -> m [Result]) -> m ()
- withK8SMinioS3Server' :: forall m context. (Typeable context, MonadFail m, KubernetesBasic context m) => FilePath -> KubernetesClusterContext -> MinioOperatorContext -> MinioS3ServerOptions -> (TestS3Server -> m [Result]) -> m ()
- data MinioS3ServerOptions = MinioS3ServerOptions {}
- defaultMinioS3ServerOptions :: Text -> MinioS3ServerOptions
- data NetworkPolicies = NetworkPolicies {}
- testS3Server :: Label "testS3Server" TestS3Server
- data TestS3Server = TestS3Server {}
- type HasTestS3Server context = HasLabel context "testS3Server" TestS3Server
- data NetworkAddress
Documentation
introduceK8SMinioS3Server Source #
Arguments
:: forall context (m :: Type -> Type). (Typeable context, KubectlBasicWithoutReader context m, HasMinioOperatorContext context) | |
=> MinioS3ServerOptions | Options |
-> SpecFree (LabelValue "testS3Server" TestS3Server :> context) m () | |
-> SpecFree context m () |
Introduce a MinIO server on a Kubernetes cluster.
Must have a minioOperator
context.
introduceK8SMinioS3Server' Source #
Arguments
:: forall context (m :: Type -> Type). (Typeable context, KubectlBasic context m, HasMinioOperatorContext context) | |
=> KubernetesClusterContext | |
-> MinioS3ServerOptions | Options |
-> SpecFree (LabelValue "testS3Server" TestS3Server :> context) m () | |
-> SpecFree context m () |
Same as introduceK8SMinioS3Server
, but allows you to pass in the KubernetesClusterContext
.
Bracket-style variants
Arguments
:: (Typeable context, MonadFail m, KubernetesBasic context m, HasFile context "kubectl") | |
=> KubernetesClusterContext | |
-> MinioOperatorContext | |
-> MinioS3ServerOptions | Options |
-> (TestS3Server -> m [Result]) | |
-> m () |
Bracket-style variant of introduceK8SMinioS3Server
.
withK8SMinioS3Server' Source #
Arguments
:: forall m context. (Typeable context, MonadFail m, KubernetesBasic context m) | |
=> FilePath | Path to kubectl binary |
-> KubernetesClusterContext | |
-> MinioOperatorContext | |
-> MinioS3ServerOptions | Options |
-> (TestS3Server -> m [Result]) | |
-> m () |
Same as withK8SMinioS3Server
, but allows you to pass in the kubectl
binary.
Types
data MinioS3ServerOptions Source #
Constructors
MinioS3ServerOptions | |
Fields
|
data NetworkPolicies Source #
Constructors
NetworkPolicies | |
Fields |
Instances
Show NetworkPolicies Source # | |
Defined in Test.Sandwich.Contexts.Kubernetes.MinioS3Server Methods showsPrec :: Int -> NetworkPolicies -> ShowS # show :: NetworkPolicies -> String # showList :: [NetworkPolicies] -> ShowS # | |
Eq NetworkPolicies Source # | |
Defined in Test.Sandwich.Contexts.Kubernetes.MinioS3Server Methods (==) :: NetworkPolicies -> NetworkPolicies -> Bool # (/=) :: NetworkPolicies -> NetworkPolicies -> Bool # |
Re-exports
testS3Server :: Label "testS3Server" TestS3Server #
data TestS3Server #
A generic test S3 server. This can be used by downstream packages like sandwich-contexts-minio.
Constructors
TestS3Server | |
Fields
|
Instances
Show TestS3Server # | |
Defined in Test.Sandwich.Contexts.Types.S3 Methods showsPrec :: Int -> TestS3Server -> ShowS # show :: TestS3Server -> String # showList :: [TestS3Server] -> ShowS # | |
Eq TestS3Server # | |
Defined in Test.Sandwich.Contexts.Types.S3 |
type HasTestS3Server context = HasLabel context "testS3Server" TestS3Server #
data NetworkAddress #
Constructors
NetworkAddressTCP | |
NetworkAddressUnix | |
Fields |
Instances
Show NetworkAddress # | |
Defined in Test.Sandwich.Contexts.Types.Network Methods showsPrec :: Int -> NetworkAddress -> ShowS # show :: NetworkAddress -> String # showList :: [NetworkAddress] -> ShowS # | |
Eq NetworkAddress # | |
Defined in Test.Sandwich.Contexts.Types.Network Methods (==) :: NetworkAddress -> NetworkAddress -> Bool # (/=) :: NetworkAddress -> NetworkAddress -> Bool # |