| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
TestContainers.Tasty
Synopsis
- ingredient :: Ingredient
- withContainers :: forall a. (forall m. MonadDocker m => m a) -> (IO a -> TestTree) -> TestTree
- (&) :: a -> (a -> b) -> b
- runResourceT :: MonadUnliftIO m => ResourceT m a -> m a
- type ResIO = ResourceT IO
- type InspectOutput = Value
- data Container
- data Image
- data Pipe
- newtype TimeoutException = TimeoutException {
- id :: ContainerId
- newtype UnexpectedEndOfPipe = UnexpectedEndOfPipe {
- id :: ContainerId
- data WaitUntilReady
- data ToImage
- type ImageTag = Text
- data ContainerRequest
- type MonadDocker m = (MonadIO m, MonadMask m, MonadThrow m, MonadCatch m, MonadResource m, MonadReader Config m)
- data DockerException
- = DockerException { }
- | InspectUnknownContainerId {
- id :: ContainerId
- | InspectOutputInvalidJSON {
- id :: ContainerId
- | InspectOutputUnexpected {
- id :: ContainerId
- | UnknownPortMapping {
- id :: ContainerId
- port :: Text
- data Config = Config {}
- data Tracer
- pattern TraceOpenSocket :: Text -> Int -> Maybe IOException -> Trace
- pattern TraceWaitUntilReady :: Maybe Int -> Trace
- pattern TraceDockerStderr :: Text -> Trace
- pattern TraceDockerInvocation :: [Text] -> Text -> ExitCode -> Trace
- pattern TraceDockerStdout :: Text -> Trace
- newTracer :: (Trace -> IO ()) -> Tracer
- defaultDockerConfig :: Config
- determineConfig :: IO Config
- containerRequest :: ToImage -> ContainerRequest
- setName :: Text -> ContainerRequest -> ContainerRequest
- setCmd :: [Text] -> ContainerRequest -> ContainerRequest
- setRm :: Bool -> ContainerRequest -> ContainerRequest
- setEnv :: [(Text, Text)] -> ContainerRequest -> ContainerRequest
- setLink :: [ContainerId] -> ContainerRequest -> ContainerRequest
- setExpose :: [Int] -> ContainerRequest -> ContainerRequest
- setWaitingFor :: WaitUntilReady -> ContainerRequest -> ContainerRequest
- run :: MonadDocker m => ContainerRequest -> m Container
- kill :: MonadDocker m => Container -> m ()
- stop :: MonadDocker m => Container -> m ()
- rm :: MonadDocker m => Container -> m ()
- withLogs :: forall m a. MonadDocker m => Container -> (Handle -> Handle -> m a) -> m a
- build :: MonadDocker m => ToImage -> m ToImage
- fromTag :: ImageTag -> ToImage
- fromBuildContext :: FilePath -> Maybe FilePath -> ToImage
- waitUntilTimeout :: Int -> WaitUntilReady -> WaitUntilReady
- waitUntilMappedPortReachable :: Int -> WaitUntilReady
- waitWithLogs :: (Container -> Handle -> Handle -> IO ()) -> WaitUntilReady
- waitForLogLine :: Pipe -> (Text -> Bool) -> WaitUntilReady
- imageTag :: Image -> ImageTag
- containerImage :: Container -> Image
- containerReleaseKey :: Container -> ReleaseKey
- containerIp :: Container -> Text
- containerPort :: Container -> Int -> Int
- inspect :: MonadDocker m => Container -> m InspectOutput
- dockerHostOs :: MonadDocker m => m Text
- isDockerOnLinux :: MonadDocker m => m Bool
- redis :: ToImage
- mongo :: ToImage
Tasty Ingredient
ingredient :: Ingredient Source #
Tasty Ingredient that adds useful options to control defaults within the
TetContainers library.
main :: IO () main =defaultMainWithIngredients(ingredient:defaultIngredients) tests
Since: 0.3.0.0
Running containers for tests
withContainers :: forall a. (forall m. MonadDocker m => m a) -> (IO a -> TestTree) -> TestTree Source #
Re-exports for convenience
runResourceT :: MonadUnliftIO m => ResourceT m a -> m a #
Unwrap a ResourceT transformer, and call all registered release actions.
Note that there is some reference counting involved due to resourceForkIO.
If multiple threads are sharing the same collection of resources, only the
last call to runResourceT will deallocate the resources.
NOTE Since version 1.2.0, this function will throw a
ResourceCleanupException if any of the cleanup functions throw an
exception.
Since: resourcet-0.3.0
type InspectOutput = Value Source #
The parsed JSON output of docker inspect command.
Since: 0.1.0.0
Handle to a Docker image.
Since: 0.1.0.0
A data type indicating which pipe to scan for a specific log line.
Since: 0.1.0.0
newtype TimeoutException Source #
The exception thrown by waitUntilTimeout.
Since: 0.1.0.0
Constructors
| TimeoutException | |
Fields
| |
Instances
| Eq TimeoutException Source # | |
Defined in TestContainers.Docker Methods (==) :: TimeoutException -> TimeoutException -> Bool # (/=) :: TimeoutException -> TimeoutException -> Bool # | |
| Show TimeoutException Source # | |
Defined in TestContainers.Docker Methods showsPrec :: Int -> TimeoutException -> ShowS # show :: TimeoutException -> String # showList :: [TimeoutException] -> ShowS # | |
| Exception TimeoutException Source # | |
Defined in TestContainers.Docker Methods toException :: TimeoutException -> SomeException # | |
newtype UnexpectedEndOfPipe Source #
The exception thrown by waitForLine in case the expected log line
wasn't found.
Since: 0.1.0.0
Constructors
| UnexpectedEndOfPipe | |
Fields
| |
Instances
| Eq UnexpectedEndOfPipe Source # | |
Defined in TestContainers.Docker Methods (==) :: UnexpectedEndOfPipe -> UnexpectedEndOfPipe -> Bool # (/=) :: UnexpectedEndOfPipe -> UnexpectedEndOfPipe -> Bool # | |
| Show UnexpectedEndOfPipe Source # | |
Defined in TestContainers.Docker Methods showsPrec :: Int -> UnexpectedEndOfPipe -> ShowS # show :: UnexpectedEndOfPipe -> String # showList :: [UnexpectedEndOfPipe] -> ShowS # | |
| Exception UnexpectedEndOfPipe Source # | |
Defined in TestContainers.Docker Methods toException :: UnexpectedEndOfPipe -> SomeException # fromException :: SomeException -> Maybe UnexpectedEndOfPipe # | |
data WaitUntilReady Source #
A strategy that describes how to asses readiness of a Container. Allows
Users to plug in their definition of readiness.
Since: 0.1.0.0
data ContainerRequest Source #
Parameters for a running a Docker container.
Since: 0.1.0.0
type MonadDocker m = (MonadIO m, MonadMask m, MonadThrow m, MonadCatch m, MonadResource m, MonadReader Config m) Source #
Docker related functionality is parameterized over this Monad.
Since: 0.1.0.0
data DockerException Source #
Failing to interact with Docker results in this exception being thrown.
Since: 0.1.0.0
Constructors
| DockerException | |
| InspectUnknownContainerId | |
Fields
| |
| InspectOutputInvalidJSON | |
Fields
| |
| InspectOutputUnexpected | |
Fields
| |
| UnknownPortMapping | |
Fields
| |
Instances
| Eq DockerException Source # | |
Defined in TestContainers.Docker Methods (==) :: DockerException -> DockerException -> Bool # (/=) :: DockerException -> DockerException -> Bool # | |
| Show DockerException Source # | |
Defined in TestContainers.Docker Methods showsPrec :: Int -> DockerException -> ShowS # show :: DockerException -> String # showList :: [DockerException] -> ShowS # | |
| Exception DockerException Source # | |
Defined in TestContainers.Docker Methods toException :: DockerException -> SomeException # | |
Configuration for defaulting behavior.
Since: 0.2.0.0
Constructors
| Config | |
Fields
| |
Traces execution within testcontainers library.
pattern TraceOpenSocket :: Text -> Int -> Maybe IOException -> Trace Source #
Opening socket
pattern TraceWaitUntilReady :: Maybe Int -> Trace Source #
Waiting for a container to become ready. Attached with the timeout to wait (in seconds).
pattern TraceDockerStderr :: Text -> Trace Source #
Line written to STDERR by a Docker process.
pattern TraceDockerInvocation :: [Text] -> Text -> ExitCode -> Trace Source #
The low-level invocation of docker command
TraceDockerInvocation args stdin exitcode
pattern TraceDockerStdout :: Text -> Trace Source #
Line written to STDOUT by a Docker process.
defaultDockerConfig :: Config Source #
Default configuration.
Since: 0.2.0.0
determineConfig :: IO Config Source #
Autoselect the default configuration depending on wether you use Docker For Mac or not.
containerRequest :: ToImage -> ContainerRequest Source #
Default ContainerRequest. Used as base for every Docker container.
Since: 0.1.0.0
setName :: Text -> ContainerRequest -> ContainerRequest Source #
Set the name of a Docker container. This is equivalent to invoking docker run
with the --name parameter.
Since: 0.1.0.0
setCmd :: [Text] -> ContainerRequest -> ContainerRequest Source #
The command to execute inside the Docker container. This is the equivalent
of passing the command on the docker run invocation.
Since: 0.1.0.0
setRm :: Bool -> ContainerRequest -> ContainerRequest Source #
Wether to remove the container once exited. This is equivalent to passing
--rm to docker run. (default is True).
Since: 0.1.0.0
setEnv :: [(Text, Text)] -> ContainerRequest -> ContainerRequest Source #
Set the environment for the container. This is equivalent to passing --env key=value
to docker run.
Since: 0.1.0.0
setLink :: [ContainerId] -> ContainerRequest -> ContainerRequest Source #
Set link on the container. This is equivalent to passing --link other_container
to docker run.
Since: 0.1.0.0
setExpose :: [Int] -> ContainerRequest -> ContainerRequest Source #
Set exposed ports on the container. This is equivalent to setting --publish $PORT to
docker run. Docker assigns a random port for the host port. You will have to use containerIp
and containerPort to connect to the published port.
container <-run$containerRequestredis&setExpose[ 6379 ] let (redisHost, redisPort) = (containerIpcontainer,containerPortcontainer 6379) print (redisHost, redisPort)
Since: 0.1.0.0
setWaitingFor :: WaitUntilReady -> ContainerRequest -> ContainerRequest Source #
Set the waiting strategy on the container. Depending on a Docker container
it can take some time until the provided service is ready. You will want to
use to setWaitingFor to block until the container is ready to use.
Since: 0.1.0.0
run :: MonadDocker m => ContainerRequest -> m Container Source #
Runs a Docker container from an Image and ContainerRequest. A finalizer
is registered so that the container is aways stopped when it goes out of scope.
This function is essentially docker run.
Since: 0.1.0.0
kill :: MonadDocker m => Container -> m () Source #
Kills a Docker container. kill is essentially docker kill.
Since: 0.1.0.0
stop :: MonadDocker m => Container -> m () Source #
Stops a Docker container. stop is essentially docker stop.
Since: 0.1.0.0
rm :: MonadDocker m => Container -> m () Source #
Remove a Docker container. rm is essentially docker rm -f
Since: 0.1.0.0
withLogs :: forall m a. MonadDocker m => Container -> (Handle -> Handle -> m a) -> m a Source #
Access STDOUT and STDERR of a running Docker container. This is essentially
docker logs under the hood.
Since: 0.1.0.0
build :: MonadDocker m => ToImage -> m ToImage Source #
Build the Image referred to by the argument. If the construction of the
image is expensive (e.g. a call to fromBuildContext) we don't want to
repeatedly build the image. Instead, build can be used to execute the
underlying Docker build once and re-use the resulting Image.
Since: 0.1.0.0
fromBuildContext :: FilePath -> Maybe FilePath -> ToImage Source #
Build the image from a build path and an optional path to the Dockerfile (default is Dockerfile)
Since: 0.1.0.0
waitUntilTimeout :: Int -> WaitUntilReady -> WaitUntilReady Source #
waitUntilTimeout n waitUntilReady waits n seconds for the container
to be ready. If the container is not ready by then a TimeoutException will
be thrown.
Since: 0.1.0.0
waitUntilMappedPortReachable :: Int -> WaitUntilReady Source #
Waits until the port of a container is ready to accept connections.
This combinator should always be used with waitUntilTimeout.
Since: 0.1.0.0
waitWithLogs :: (Container -> Handle -> Handle -> IO ()) -> WaitUntilReady Source #
A low-level primitive that allows scanning the logs for specific log lines that indicate readiness of a container.
The Handles passed to the function argument represent stdout and stderr
of the container.
Since: 0.1.0.0
waitForLogLine :: Pipe -> (Text -> Bool) -> WaitUntilReady Source #
Waits for a specific line to occur in the logs. Throws a UnexpectedEndOfPipe
exception in case the desired line can not be found on the logs.
Say you want to find "Ready to accept connections" in the logs on Stdout try:
waitForLogLine Stdout ("Ready to accept connections" `isInfixOf`)
Since: 0.1.0.0
imageTag :: Image -> ImageTag Source #
The image tag assigned by Docker. Uniquely identifies an Image
within Docker.
Since: 0.1.0.0
containerImage :: Container -> Image Source #
Returns the underlying image of the container.
Since: 0.1.0.0
containerReleaseKey :: Container -> ReleaseKey Source #
Returns the internal release key used for safely shutting down the container. Use this with care. This function is considered an internal detail.
Since: 0.1.0.0
containerIp :: Container -> Text Source #
Looks up the ip address of the container.
Since: 0.1.0.0
containerPort :: Container -> Int -> Int Source #
Looks up an exposed port on the host.
Since: 0.1.0.0
inspect :: MonadDocker m => Container -> m InspectOutput Source #
Runs the `docker inspect` command. Memoizes the result.
Since: 0.1.0.0
dockerHostOs :: MonadDocker m => m Text Source #
isDockerOnLinux :: MonadDocker m => m Bool Source #