testcontainers-0.3.0.0: Docker containers for your integration tests.
Safe HaskellNone
LanguageHaskell2010

TestContainers

Description

This module shall be used as entrypoint to the testcontainers library. It exports all the necessary types and functions for most common use-cases.

Synopsis

Docker images

type ImageTag = Text Source #

A tag to a Docker image.

Since: 0.1.0.0

data Image Source #

Handle to a Docker image.

Since: 0.1.0.0

Instances

Instances details
Eq Image Source # 
Instance details

Defined in TestContainers.Docker

Methods

(==) :: Image -> Image -> Bool #

(/=) :: Image -> Image -> Bool #

Show Image Source # 
Instance details

Defined in TestContainers.Docker

Methods

showsPrec :: Int -> Image -> ShowS #

show :: Image -> String #

showList :: [Image] -> ShowS #

imageTag :: Image -> ImageTag Source #

The image tag assigned by Docker. Uniquely identifies an Image within Docker.

Since: 0.1.0.0

Referring to Docker images

data ToImage Source #

A description of how to build an Image.

Since: 0.1.0.0

fromTag :: ImageTag -> ToImage Source #

Get an Image from a tag.

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

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

docker run parameters

data ContainerRequest Source #

Parameters for a running a Docker container.

Since: 0.1.0.0

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 $ containerRequest redis & setExpose [ 6379 ]
  let (redisHost, redisPort) = (containerIp container, containerPort container 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

Running Docker containers (docker run)

data Container Source #

Handle to a Docker container.

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

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

containerImage :: Container -> Image Source #

Returns the underlying image of the container.

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

Inspecting Docker containers

type InspectOutput = Value Source #

The parsed JSON output of docker inspect command.

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

Docker container lifecycle

stop :: MonadDocker m => Container -> m () Source #

Stops a Docker container. stop is essentially docker stop.

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

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

Readiness checks

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

Timeout for readiness checks

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

Waiting on particular log lines

data Pipe Source #

A data type indicating which pipe to scan for a specific log line.

Since: 0.1.0.0

Constructors

Stdout

Refer to logs on STDOUT.

Stderr

Refer to logs on STDERR.

Instances

Instances details
Eq Pipe Source # 
Instance details

Defined in TestContainers.Docker

Methods

(==) :: Pipe -> Pipe -> Bool #

(/=) :: Pipe -> Pipe -> Bool #

Ord Pipe Source # 
Instance details

Defined in TestContainers.Docker

Methods

compare :: Pipe -> Pipe -> Ordering #

(<) :: Pipe -> Pipe -> Bool #

(<=) :: Pipe -> Pipe -> Bool #

(>) :: Pipe -> Pipe -> Bool #

(>=) :: Pipe -> Pipe -> Bool #

max :: Pipe -> Pipe -> Pipe #

min :: Pipe -> Pipe -> Pipe #

Show Pipe Source # 
Instance details

Defined in TestContainers.Docker

Methods

showsPrec :: Int -> Pipe -> ShowS #

show :: Pipe -> String #

showList :: [Pipe] -> ShowS #

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:

wairForLogLine Stdout ("Ready to accept connections" `isInfixOf`)

Since: 0.1.0.0

Wait until connection can be established

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

Monad

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

Configuration

data Config Source #

Configuration for defaulting behavior.

Since: 0.2.0.0

Constructors

Config 

Fields

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.

data Tracer Source #

Traces execution within testcontainers library.

Instances

Instances details
Semigroup Tracer Source # 
Instance details

Defined in TestContainers.Docker

Monoid Tracer Source # 
Instance details

Defined in TestContainers.Docker

data Trace Source #

Type representing various events during testcontainer execution.

Constructors

TraceDockerInvocation [Text] Text ExitCode

The low-level invocation of docker command

  TraceDockerInvocation args stdin exitcode
TraceDockerStdout Text

Line written to STDOUT by a Docker process.

TraceDockerStderr Text

Line written to STDERR by a Docker process.

TraceWaitUntilReady (Maybe Int)

Waiting for a container to become ready. Attached with the timeout to wait (in seconds).

TraceOpenSocket Text Int (Maybe IOException)

Opening socket

Instances

Instances details
Eq Trace Source # 
Instance details

Defined in TestContainers.Docker

Methods

(==) :: Trace -> Trace -> Bool #

(/=) :: Trace -> Trace -> Bool #

Show Trace Source # 
Instance details

Defined in TestContainers.Docker

Methods

showsPrec :: Int -> Trace -> ShowS #

show :: Trace -> String #

showList :: [Trace] -> ShowS #

newTracer :: (Trace -> IO ()) -> Tracer Source #

Construct a new Tracer from a tracing function.

Exceptions

data DockerException Source #

Failing to interact with Docker results in this exception being thrown.

Since: 0.1.0.0

Constructors

DockerException 

Fields

InspectUnknownContainerId 

Fields

InspectOutputInvalidJSON 

Fields

InspectOutputUnexpected 

Fields

UnknownPortMapping 

Fields

  • id :: ContainerId

    Id of the Container that we tried to lookup the port mapping.

  • port :: Text

    Textual representation of port mapping we were trying to look up.

newtype TimeoutException Source #

The exception thrown by waitUntilTimeout.

Since: 0.1.0.0

Constructors

TimeoutException 

Fields

  • id :: ContainerId

    The id of the underlying container that was not ready in time.

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

Misc. Docker functions

Predefined Docker images

redis :: ToImage Source #

Image for Redis database.

redis = fromTag "redis:5.0"

Since: 0.1.0.0

mongo :: ToImage Source #

Image for Mongo database.

mongo = Tag "mongo:4.0.17"

Since: 0.1.0.0

Reexports

type ResIO = ResourceT IO #

Convenient alias for ResourceT IO.

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

(&) :: a -> (a -> b) -> b infixl 1 #

& is a reverse application operator. This provides notational convenience. Its precedence is one higher than that of the forward application operator $, which allows & to be nested in $.

>>> 5 & (+1) & show
"6"

Since: base-4.8.0.0