| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Test.Sandwich.Contexts.MinIO
Description
MinIO is a popular S3-compatible object storage system. This module provides some tools to introduce it, either as a raw binary or via a container system.
The MinIO server will be introduced as a generic TestS3Server. This gives you the ability to easily swap out different S3-compatible stores in your tests.
Synopsis
- introduceMinIOViaNix :: forall context (m :: Type -> Type). (HasBaseContext context, HasNixContext context, MonadMask m, MonadUnliftIO m) => MinIOContextOptions -> SpecFree (LabelValue "testS3Server" TestS3Server :> (LabelValue (AppendSymbol "file-" "minio") (EnvironmentFile "minio") :> context)) m () -> SpecFree context m ()
- introduceMinIOViaBinary :: forall context (m :: Type -> Type). (HasBaseContext context, HasFile context "minio", MonadMask m, MonadUnliftIO m) => MinIOContextOptions -> SpecFree (LabelValue "testS3Server" TestS3Server :> context) m () -> SpecFree context m ()
- introduceMinIOViaContainer :: forall context (m :: Type -> Type). (HasBaseContext context, MonadMask m, MonadUnliftIO m) => MinIOContextOptions -> ContainerOptions -> SpecFree (LabelValue "testS3Server" TestS3Server :> context) m () -> SpecFree context m ()
- withMinIOViaBinary :: (HasBaseContextMonad context m, HasFile context "minio", MonadLoggerIO m, MonadMask m, MonadUnliftIO m) => MinIOContextOptions -> (TestS3Server -> m [Result]) -> m ()
- withMinIOViaBinary' :: (HasBaseContextMonad context m, MonadLoggerIO m, MonadMask m, MonadUnliftIO m) => FilePath -> MinIOContextOptions -> (TestS3Server -> m [Result]) -> m ()
- withMinIOViaContainer :: (HasBaseContextMonad context m, MonadLoggerIO m, MonadMask m, MonadUnliftIO m) => MinIOContextOptions -> ContainerOptions -> (TestS3Server -> m [Result]) -> m ()
- testS3ServerEndpoint :: TestS3Server -> Text
- testS3ServerContainerEndpoint :: TestS3Server -> Maybe Text
- testS3ServerConnectInfo :: TestS3Server -> ConnectInfo
- testS3Server :: Label "testS3Server" TestS3Server
- data TestS3Server = TestS3Server {}
- type HasTestS3Server context = HasLabel context "testS3Server" TestS3Server
- data ContainerOptions = ContainerOptions {}
- defaultContainerOptions :: ContainerOptions
- data HttpMode
- data NetworkAddress
- data MinIOContextOptions = MinIOContextOptions {}
- defaultMinIOContextOptions :: MinIOContextOptions
Introducing MinIO
Arguments
| :: forall context (m :: Type -> Type). (HasBaseContext context, HasNixContext context, MonadMask m, MonadUnliftIO m) | |
| => MinIOContextOptions | Options |
| -> SpecFree (LabelValue "testS3Server" TestS3Server :> (LabelValue (AppendSymbol "file-" "minio") (EnvironmentFile "minio") :> context)) m () | |
| -> SpecFree context m () |
Introduce a MinIO server, deriving the MinIO binary from the Nix context.
introduceMinIOViaBinary Source #
Arguments
| :: forall context (m :: Type -> Type). (HasBaseContext context, HasFile context "minio", MonadMask m, MonadUnliftIO m) | |
| => MinIOContextOptions | Options |
| -> SpecFree (LabelValue "testS3Server" TestS3Server :> context) m () | |
| -> SpecFree context m () |
Introduce a MinIO server, assuming the binary is already available as a HasFile context.
introduceMinIOViaContainer Source #
Arguments
| :: forall context (m :: Type -> Type). (HasBaseContext context, MonadMask m, MonadUnliftIO m) | |
| => MinIOContextOptions | Options |
| -> ContainerOptions | |
| -> SpecFree (LabelValue "testS3Server" TestS3Server :> context) m () | |
| -> SpecFree context m () |
Introduce a MinIO server by launching a container.
Lower-level versions
Arguments
| :: (HasBaseContextMonad context m, HasFile context "minio", MonadLoggerIO m, MonadMask m, MonadUnliftIO m) | |
| => MinIOContextOptions | Options |
| -> (TestS3Server -> m [Result]) | |
| -> m () |
Bracket-style variant of introduceMinIOViaBinary.
Arguments
| :: (HasBaseContextMonad context m, MonadLoggerIO m, MonadMask m, MonadUnliftIO m) | |
| => FilePath | Path to the |
| -> MinIOContextOptions | |
| -> (TestS3Server -> m [Result]) | |
| -> m () |
Introduce a MinIO server by manually providing the path to the binary.
withMinIOViaContainer Source #
Arguments
| :: (HasBaseContextMonad context m, MonadLoggerIO m, MonadMask m, MonadUnliftIO m) | |
| => MinIOContextOptions | Options |
| -> ContainerOptions | |
| -> (TestS3Server -> m [Result]) | |
| -> m () |
Bracket-style variant of introduceMinIOViaContainer.
Helpers for constructing connections
testS3ServerEndpoint :: TestS3Server -> Text #
Generate an S3 connection string for the given server.
testS3ServerContainerEndpoint :: TestS3Server -> Maybe Text #
Generate an S3 connection string for the given containerized server, for the network address inside the container.
Returns Nothing if this server isn't containerized.
testS3ServerConnectInfo :: TestS3Server -> ConnectInfo Source #
Construct a ConnectInfo (from the minio-hs package) for the given TestS3Server.
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 ContainerOptions #
Type to represent generic options for launching containers.
Constructors
| ContainerOptions | |
Instances
| Show ContainerOptions # | |
Defined in Test.Sandwich.Contexts.Container Methods showsPrec :: Int -> ContainerOptions -> ShowS # show :: ContainerOptions -> String # showList :: [ContainerOptions] -> ShowS # | |
| Eq ContainerOptions # | |
Defined in Test.Sandwich.Contexts.Container Methods (==) :: ContainerOptions -> ContainerOptions -> Bool # (/=) :: ContainerOptions -> ContainerOptions -> Bool # | |
Constructors
| HttpModeHttp | |
| HttpModeHttps | |
| HttpModeHttpsNoValidate | A special mode to allow a server to run in HTTPS mode, but connect to it without HTTPS validation. Useful for tests. |
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 # | |
Types
data MinIOContextOptions Source #
Constructors
| MinIOContextOptions | |
Fields
| |
Instances
| Show MinIOContextOptions Source # | |
Defined in Test.Sandwich.Contexts.MinIO Methods showsPrec :: Int -> MinIOContextOptions -> ShowS # show :: MinIOContextOptions -> String # showList :: [MinIOContextOptions] -> ShowS # | |
| Eq MinIOContextOptions Source # | |
Defined in Test.Sandwich.Contexts.MinIO Methods (==) :: MinIOContextOptions -> MinIOContextOptions -> Bool # (/=) :: MinIOContextOptions -> MinIOContextOptions -> Bool # | |