testcontainers-0.1.0.0: Docker containers for your integration tests.

Safe HaskellNone
LanguageHaskell2010

TestContainers.Docker

Contents

Synopsis

Documentation

type MonadDocker m = (MonadIO m, MonadMask m, MonadThrow m, MonadCatch m, MonadResource m) Source #

Docker related functionality is parameterized over this Monad.

Docker image

type ImageTag = Text Source #

A tag to a Docker image.

data Image Source #

Handle to a Docker image.

Instances
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.

Docker container

type ContainerId = Text Source #

Identifies a container within the Docker runtime. Assigned by docker run.

data Container Source #

Handle to a Docker container.

containerId :: Container -> ContainerId Source #

Returns the id of the container.

containerImage :: Container -> Image Source #

Returns the underlying image of the container.

containerIp :: Container -> Text Source #

Looks up the ip address of the container.

containerPort :: Container -> Int -> Int Source #

Looks up an exposed port on the host.

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.

Referring to images

data ToImage Source #

A description of how to build an Image.

fromTag :: ImageTag -> ToImage Source #

Get an Image from a tag.

fromBuildContext :: FilePath -> Maybe FilePath -> ToImage Source #

Build the image from a build path and an optional path to the Dockerfile (default is Dockerfile)

fromDockerfile :: Text -> ToImage Source #

Build a contextless image only from a Dockerfile passed as Text.

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.

Exceptions

data DockerException Source #

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

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.

Running containers

data ContainerRequest Source #

Parameters for a running a Docker container.

containerRequest :: ToImage -> ContainerRequest Source #

Default ContainerRequest. Used as base for every Docker container.

setName :: Text -> ContainerRequest -> ContainerRequest Source #

Set the name of a Docker container.

setCmd :: [Text] -> ContainerRequest -> ContainerRequest Source #

The command to execute inside the Docker container.

setRm :: Bool -> ContainerRequest -> ContainerRequest Source #

Wether to remove the container once exited.

setEnv :: [(Text, Text)] -> ContainerRequest -> ContainerRequest Source #

Set the environment for the container.

setLink :: [ContainerId] -> ContainerRequest -> ContainerRequest Source #

Set link on the container.

setExpose :: [Int] -> ContainerRequest -> ContainerRequest Source #

Set exposed ports on the container.

Example:

 redis
     & setExpose [ 6379 ]

setWaitingFor :: WaitUntilReady -> ContainerRequest -> ContainerRequest Source #

Set the waiting strategy on the container.

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.

Managing the container lifecycle

type InspectOutput = Value Source #

The parsed JSON output of docker inspect command.

inspect :: MonadDocker m => Container -> m InspectOutput Source #

Runs the `docker inspect` command. Memoizes the result.

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

Stops a Docker container.

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

Kills a Docker container.

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

Remove a Docker container.

withLogs :: forall m a. MonadDocker m => Container -> (Handle -> Handle -> m a) -> m a Source #

Get the logs from a Docker container.

Wait for containers to become ready

data WaitUntilReady Source #

A strategy that describes how to asses readiness of a Container. Allows Users to plug in their definition of readiness.

waitUntilReady :: MonadDocker m => Container -> WaitUntilReady -> m () Source #

Blocks until the container is ready. waitUntilReady might throw exceptions depending on the used WaitUntilReady on the container.

Only block for defined amounts of time

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.

Wait until a specific pattern appears in the logs

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.

newtype UnexpectedEndOfPipe Source #

The exception thrown by waitForLine in case the expected log line wasn't found.

Constructors

UnexpectedEndOfPipe 

Fields

data Pipe Source #

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

Constructors

Stdout

Refer to logs on STDOUT.

Stderr

Refer to logs on STDERR.

Instances
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 #

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`)

Wait until a socket is reachable

waitUntilMappedPortReachable :: Int -> WaitUntilReady Source #

Waits until the port of a container is ready to accept connections. This combinator should always be used with waitUntilTimeout.

Reexports for convenience

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