distributed-process-systest-0.1.1: Cloud Haskell Test Support

Copyright(c) Tim Watson 2014 - 2016
LicenseBSD3 (see the file LICENSE)
MaintainerTim Watson
Stabilityexperimental
Portabilitynon-portable (requires concurrency)
Safe HaskellNone
LanguageHaskell98

Control.Distributed.Process.SysTest.Utils

Description

This module provides basic building blocks for testing Cloud Haskell programs.

Synopsis

Documentation

type TestResult a = MVar a Source #

A mutable cell containing a test result.

data Ping Source #

A simple Ping signal

Constructors

Ping 

Instances

Eq Ping Source # 

Methods

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

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

Show Ping Source # 

Methods

showsPrec :: Int -> Ping -> ShowS #

show :: Ping -> String #

showList :: [Ping] -> ShowS #

Generic Ping Source # 

Associated Types

type Rep Ping :: * -> * #

Methods

from :: Ping -> Rep Ping x #

to :: Rep Ping x -> Ping #

Binary Ping Source # 

Methods

put :: Ping -> Put #

get :: Get Ping #

putList :: [Ping] -> Put #

type Rep Ping Source # 
type Rep Ping = D1 (MetaData "Ping" "Control.Distributed.Process.SysTest.Utils" "distributed-process-systest-0.1.1-i3WPsUfanj2oIjVVAsCNH" False) (C1 (MetaCons "Ping" PrefixI False) U1)

shouldBe :: a -> Matcher a -> Process () Source #

shouldContain :: (Show a, Eq a) => [a] -> a -> Process () Source #

shouldNotContain :: (Show a, Eq a) => [a] -> a -> Process () Source #

data TestProcessControl Source #

Control signals used to manage test processes

Instances

Generic TestProcessControl Source # 
Binary TestProcessControl Source # 
type Rep TestProcessControl Source # 
type Rep TestProcessControl = D1 (MetaData "TestProcessControl" "Control.Distributed.Process.SysTest.Utils" "distributed-process-systest-0.1.1-i3WPsUfanj2oIjVVAsCNH" False) ((:+:) (C1 (MetaCons "Stop" PrefixI False) U1) ((:+:) (C1 (MetaCons "Go" PrefixI False) U1) (C1 (MetaCons "Report" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ProcessId)))))

startTestProcess :: Process () -> Process ProcessId Source #

Starts a test process on the local node.

runTestProcess :: Process () -> Process () Source #

Runs a test process around the supplied proc, which is executed whenever the outer process loop receives a Go signal.

testProcessGo :: ProcessId -> Process () Source #

Tell a test process to continue executing

testProcessStop :: ProcessId -> Process () Source #

Tell a test process to stop (i.e., terminate)

testProcessReport :: ProcessId -> Process () Source #

Tell a test process to send a report (message) back to the calling process

delayedAssertion :: Eq a => String -> LocalNode -> a -> (TestResult a -> Process ()) -> Assertion Source #

Run the supplied testProc using an MVar to collect and assert against its result. Uses the supplied note if the assertion fails.

assertComplete :: Eq a => String -> MVar a -> a -> IO () Source #

Takes the value of mv (using takeMVar) and asserts that it matches a

newLogger :: IO Logger Source #

Create a new Logger. Logger uses a TQueue to receive and process messages on a worker thread.

putLogMsg :: Logger -> String -> Process () Source #

Send a message to the Logger

stopLogger :: Logger -> IO () Source #

Stop the worker thread for the given Logger

noop :: Process () Source #

Does exactly what it says on the tin, doing so in the Process monad.

stash :: TestResult a -> a -> Process () Source #