testcontainers-0.5.1.0: Docker containers for your integration tests.
Safe HaskellSafe-Inferred
LanguageHaskell2010

TestContainers.Tasty

Synopsis

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

Re-exports for convenience

data State Source #

State of a Docker container.

Since: 0.5.0.0

data Status Source #

Status of a Docker container.

Since: 0.5.0.0

Instances

Instances details
Show Status Source # 
Instance details

Defined in TestContainers.Docker.State

Eq Status Source # 
Instance details

Defined in TestContainers.Docker.State

Methods

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

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

type ResIO = ResourceT IO #

Convenient alias for ResourceT IO.

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
Show Image Source # 
Instance details

Defined in TestContainers.Docker

Methods

showsPrec :: Int -> Image -> ShowS #

show :: Image -> String #

showList :: [Image] -> ShowS #

Eq Image Source # 
Instance details

Defined in TestContainers.Docker

Methods

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

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

data ToImage Source #

A description of how to build an Image.

Since: 0.1.0.0

data ContainerRequest Source #

Parameters for a running a Docker container.

Since: 0.1.0.0

Instances

Instances details
WithoutReaper ContainerRequest Source # 
Instance details

Defined in TestContainers.Docker

type LogConsumer = Pipe -> ByteString -> IO () Source #

An abstraction for forwarding logs.

Since: 0.5.0.0

data NetworkRequest Source #

Parameters for creating a new Docker network.

Since: 0.5.0.0

Instances

Instances details
WithoutReaper NetworkRequest Source # 
Instance details

Defined in TestContainers.Docker.Network

data Network Source #

Handle to a Docker network.

Since: 0.5.0.0

type NetworkId = Text Source #

Identifies a network within the Docker runtime. Assigned by docker network create

Since: 0.5.0.0

data Port Source #

Defintion of a Port. Allows for specifying ports using various protocols. Due to the Num and IsString instance allows for convenient Haskell literals.

>>> "80" :: Port
80/tcp
>>> "80/tcp" :: Port
80/tcp
>>> 80 :: Port
80/tcp
>>> "90/udp" :: Port
90/udp

Constructors

Port 

Fields

Instances

Instances details
IsString Port Source #

A cursed but handy instance supporting literal Ports of them form "8080", "8080/udp", "8080/tcp".

Since: 0.5.0.0

Instance details

Defined in TestContainers.Docker

Methods

fromString :: String -> Port #

Num Port Source #

A cursed but handy instance supporting literal Ports.

Since: 0.5.0.0

Instance details

Defined in TestContainers.Docker

Methods

(+) :: Port -> Port -> Port #

(-) :: Port -> Port -> Port #

(*) :: Port -> Port -> Port #

negate :: Port -> Port #

abs :: Port -> Port #

signum :: Port -> Port #

fromInteger :: Integer -> Port #

Show Port Source # 
Instance details

Defined in TestContainers.Docker

Methods

showsPrec :: Int -> Port -> ShowS #

show :: Port -> String #

showList :: [Port] -> ShowS #

Eq Port Source # 
Instance details

Defined in TestContainers.Docker

Methods

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

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

Ord Port Source # 
Instance details

Defined in TestContainers.Docker

Methods

compare :: Port -> Port -> Ordering #

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

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

(>) :: Port -> Port -> Bool #

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

max :: Port -> Port -> Port #

min :: Port -> Port -> Port #

data Container Source #

Handle to a Docker container.

Since: 0.1.0.0

type InspectOutput = Value Source #

The parsed JSON output of docker inspect command.

Since: 0.1.0.0

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 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
Show Pipe Source # 
Instance details

Defined in TestContainers.Docker.Internal

Methods

showsPrec :: Int -> Pipe -> ShowS #

show :: Pipe -> String #

showList :: [Pipe] -> ShowS #

Eq Pipe Source # 
Instance details

Defined in TestContainers.Docker.Internal

Methods

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

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

Ord Pipe Source # 
Instance details

Defined in TestContainers.Docker.Internal

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 #

type MonadDocker m = m ~ TestContainer Source #

Docker related functionality is parameterized over this Monad. Since 0.5.0.0 this is just a type alias for m ~ TestContainer.

Since: 0.1.0.0

data TestContainer a Source #

The heart and soul of the testcontainers library.

Since: 0.5.0.0

Instances

Instances details
MonadFix TestContainer Source # 
Instance details

Defined in TestContainers.Monad

Methods

mfix :: (a -> TestContainer a) -> TestContainer a #

MonadIO TestContainer Source # 
Instance details

Defined in TestContainers.Monad

Methods

liftIO :: IO a -> TestContainer a #

Applicative TestContainer Source # 
Instance details

Defined in TestContainers.Monad

Functor TestContainer Source # 
Instance details

Defined in TestContainers.Monad

Methods

fmap :: (a -> b) -> TestContainer a -> TestContainer b #

(<$) :: a -> TestContainer b -> TestContainer a #

Monad TestContainer Source # 
Instance details

Defined in TestContainers.Monad

MonadCatch TestContainer Source # 
Instance details

Defined in TestContainers.Monad

MonadMask TestContainer Source # 
Instance details

Defined in TestContainers.Monad

MonadThrow TestContainer Source # 
Instance details

Defined in TestContainers.Monad

Methods

throwM :: (HasCallStack, Exception e) => e -> TestContainer a #

MonadResource TestContainer Source # 
Instance details

Defined in TestContainers.Monad

MonadUnliftIO TestContainer Source # 
Instance details

Defined in TestContainers.Monad

Methods

withRunInIO :: ((forall a. TestContainer a -> IO a) -> IO b) -> TestContainer b #

MonadReader Config TestContainer Source # 
Instance details

Defined in TestContainers.Monad

Monoid a => Monoid (TestContainer a) Source # 
Instance details

Defined in TestContainers.Monad

Semigroup a => Semigroup (TestContainer a) Source # 
Instance details

Defined in TestContainers.Monad

data Config Source #

Configuration for defaulting behavior.

Since: 0.2.0.0

Constructors

Config 

Fields

Instances

Instances details
MonadReader Config TestContainer Source # 
Instance details

Defined in TestContainers.Monad

data Tracer Source #

Traces execution within testcontainers library.

Instances

Instances details
Monoid Tracer Source # 
Instance details

Defined in TestContainers.Trace

Semigroup Tracer Source # 
Instance details

Defined in TestContainers.Trace

data DockerException Source #

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

Since: 0.1.0.0

Constructors

DockerException 

Fields

InspectUnknownContainerId 

Fields

  • id :: ContainerId

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

InspectOutputInvalidJSON 

Fields

  • id :: ContainerId

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

InspectOutputMissingNetwork 

Fields

  • id :: ContainerId

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

InspectOutputUnexpected 

Fields

  • id :: ContainerId

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

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

pattern TraceDockerInvocation :: [Text] -> Text -> ExitCode -> Trace Source #

The low-level invocation of docker command

  TraceDockerInvocation args stdin exitcode

pattern TraceDockerFollowLogs :: [Text] -> Trace Source #

Preparations to follow the logs for a certain container

pattern TraceDockerStdout :: Text -> Trace Source #

Line written to STDOUT by a Docker process.

pattern TraceDockerStderr :: Text -> Trace Source #

Line written to STDERR by a Docker process.

pattern TraceWaitUntilReady :: Maybe Int -> Trace Source #

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

pattern TraceOpenSocket :: Text -> Int -> Maybe IOException -> Trace Source #

Opening socket

pattern TraceHttpCall :: Text -> Int -> Either String Int -> Trace Source #

Call HTTP endpoint

stop :: Container -> TestContainer () Source #

Stops a Docker container. stop is essentially docker stop.

Since: 0.1.0.0

run :: ContainerRequest -> TestContainer 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

build :: ToImage -> TestContainer 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

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

(&) :: 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

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

imageTag :: Image -> ImageTag Source #

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

Since: 0.1.0.0

fromTag :: ImageTag -> ToImage Source #

Get an Image from a tag. This runs docker pull --quiet tag to obtain an image id.

Since: 0.1.0.0

fromImageId :: Text -> ToImage Source #

Get an Image from an image id. This doesn't run docker pull or any other Docker command on construction.

Since: 0.5.1.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

containerRequest :: ToImage -> ContainerRequest Source #

Default ContainerRequest. Used as base for every Docker container.

Since: 0.1.0.0

withoutReaper :: WithoutReaper request => request -> request Source #

Do not register the docker resource (container, register, etc.) with the resource reaper. Careful, doing this will make your container leak on shutdown if not explicitly stopped.

Since: 0.5.1.0

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

Deprecated: See setFixedName

Set the name of a Docker container. This is equivalent to invoking docker run with the --name parameter.

Since: 0.1.0.0

setFixedName :: Text -> ContainerRequest -> ContainerRequest Source #

Set the name of a Docker container. This is equivalent to invoking docker run with the --name parameter.

Since: 0.5.0.0

setSuffixedName :: Text -> ContainerRequest -> ContainerRequest Source #

Set the name randomly suffixed of a Docker container. This is equivalent to invoking docker run with the --name parameter.

Since: 0.5.0.0

setRandomName :: ContainerRequest -> ContainerRequest Source #

Set the name randomly given of a Docker container. This is equivalent to omitting the --name parameter calling docker run.

Since: 0.5.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

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

The volume mounts to link to Docker container. This is the equivalent of passing the command on the docker run -v invocation.

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

setMemory :: Text -> ContainerRequest -> ContainerRequest Source #

Set the memory limit of a Docker container. This is equivalent to invoking docker run with the --memory parameter.

Since: 0.5.1.0

setCpus :: Text -> ContainerRequest -> ContainerRequest Source #

Set the cpus limit of a Docker container. This is equivalent to invoking docker run with the --cpus parameter.

Since: 0.5.1.0

withWorkingDirectory :: Text -> ContainerRequest -> ContainerRequest Source #

Sets the working directory inside the container.

Since: 0.5.1.0

withNetwork :: Network -> ContainerRequest -> ContainerRequest Source #

Set the network the container will connect to. This is equivalent to passing --network network_name to docker run.

Since: 0.5.0.0

withNetworkAlias :: Text -> ContainerRequest -> ContainerRequest Source #

Set the network alias for this container. This is equivalent to passing --network-alias alias to docker run.

Since: 0.5.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 :: [Port] -> 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

withFollowLogs :: LogConsumer -> ContainerRequest -> ContainerRequest Source #

Forwards container logs to the given LogConsumer once ran.

Since: 0.5.0.0

consoleLogConsumer :: LogConsumer Source #

A simple LogConsumer that writes log lines to stdout and stderr respectively.

Since: 0.5.0.0

networkRequest :: NetworkRequest Source #

Default parameters for creating a new Docker network.

Since: 0.5.0.0

withDriver :: Text -> NetworkRequest -> NetworkRequest Source #

Driver to manage the Network (default "bridge").

Since: 0.5.0.0

withIpv6 :: NetworkRequest -> NetworkRequest Source #

Enable IPv6 for the Docker network.

Since: 0.5.0.0

fromExistingNetwork :: NetworkId -> TestContainer Network Source #

Creates a Network from an existing NetworkId. Note that the Network is not managed by the TestContainer monad and as such is not being cleaned up afterwards.

Since: 0.5.1.0

containerAlias :: Container -> Text Source #

Get the container's network alias. Takes the first alias found.

Since: 0.5.0.0

containerGateway :: Container -> Text Source #

Get the IP address for the container's gateway, i.e. the host. Takes the first gateway address found.

Since: 0.5.0.0

containerIp :: Container -> Text Source #

Looks up the ip address of the container.

Since: 0.1.0.0

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

Looks up an exposed port on the host.

Since: 0.1.0.0

containerAddress :: Container -> Port -> (Text, Int) Source #

Returns the domain and port exposing the given container's port. Differs from containerPort in that containerAddress will return the container's domain and port if the program is running in the same network. Otherwise, containerAddress will use the exposed port on the Docker host.

Since: 0.5.0.0

containerReleaseKey :: Container -> ReleaseKey Source #

Deprecated: Containers are cleaned up with a separate resource reaper. Releasing the container manually is not going to work.

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

inspect :: Container -> TestContainer InspectOutput Source #

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

Since: 0.1.0.0

kill :: Container -> TestContainer () Source #

Kills a Docker container. kill is essentially docker kill.

Since: 0.1.0.0

rm :: Container -> TestContainer () Source #

Remove a Docker container. rm is essentially docker rm -f

Since: 0.1.0.0

withLogs :: Container -> (Handle -> Handle -> TestContainer a) -> TestContainer a Source #

Access STDOUT and STDERR of a running Docker container. This is essentially docker logs under the hood.

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

stateError :: State -> Maybe Text Source #

Since: 0.5.0.0

stateExitCode :: State -> Maybe Int Source #

Since: 0.5.0.0

stateFinishedAt :: State -> Maybe Text Source #

Since: 0.5.0.0

stateOOMKilled :: State -> Bool Source #

Whether a container was killed by the OOM killer.

Since: 0.5.0.0

statePid :: State -> Maybe Int Source #

Since: 0.5.0.0

stateStartedAt :: State -> Maybe Text Source #

Since: 0.5.0.0

stateStatus :: State -> Status Source #

Returns the Status of container.

Since: 0.5.0.0

waitForState :: (State -> Bool) -> WaitUntilReady Source #

waitForState waits for a certain state of the container. If the container reaches a terminal state InvalidStateException will be thrown.

Since: 0.5.0.0

successfulExit :: State -> Bool Source #

successfulExit is supposed to be used in conjunction with waitForState.

Since: 0.5.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

waitUntilMappedPortReachable :: Port -> 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

waitForHttp Source #

Arguments

:: Port

Port

-> String

URL path

-> [Int]

Acceptable status codes

-> WaitUntilReady 

Waits for a specific http status code. This combinator should always be used with waitUntilTimeout.

Since: 0.5.0.0

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.

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

Construct a new Tracer from a tracing function.

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