darcs-2.18.2: a distributed, interactive, smart revision control system
Safe HaskellSafe-Inferred
LanguageHaskell2010

Darcs.UI.Commands.Test.Impl

Synopsis

Documentation

class Monad m => TestRunner m where Source #

An indexed monad that can be used to run tests. TestingEnvIO is the only real implementation, the unit tests for testing are based on mock implementations.

Associated Types

type ApplyPatchReqs m (p :: * -> * -> *) :: Constraint Source #

type DisplayPatchReqs m (p :: * -> * -> *) :: Constraint Source #

Methods

writeMsg :: String -> m wX wX () Source #

Output a message

mentionPatch :: DisplayPatchReqs m p => p wA wB -> m wX wX () Source #

Output a message containing the name of a patch

applyPatch :: ApplyPatchReqs m p => p wX wY -> m wX wY () Source #

Apply a patch to the testing tree.

unapplyPatch :: ApplyPatchReqs m p => p wX wY -> m wY wX () Source #

Unapply a patch from the testing tree

getCurrentTestResult :: m wX wX (TestResult wX) Source #

Get the current status (passskipfail) of the testing tree, e.g. by running the test command.

finishedTesting :: a -> m wX TestingDone a Source #

Flag that all testing has completed.

runStrategy :: TestablePatch m p => TestStrategy -> ShrinkFailure -> RL p wOlder wNewer -> m wNewer TestingDone (StrategyResultSealed p) Source #

data TestResult wX Source #

The result of running a test on state wX of the repository.

Constructors

Testable (TestResultValid wX)

We got a usable test result.

Untestable

The test result could not be identified as either pass or fail, for example it might have been a build failure. External test scripts report this by reporting exit code 125.

data TestResultValid wX Source #

A usable test result, i.e. not an untestable state.

Constructors

Success

The test passed.

Failure (TestFailure wX)

The test failed with the given exit code.

data TestFailure wX Source #

Constructors

TestFailure Int 

data TestingDone Source #

Once we've finished tracking down a test failure, we no longer care about tracking the actual state of the testing tree. This witness constant is never used in any patch, so once we use it for the state of the testing tree, in practice we can no longer do anything more with that tree.

We could also use some kind of existential or different monad type to represent this, but it would make composing code with 'do' harder.

data PatchSeq p wX wY where Source #

PatchSeq is a sequence of patches, implemented as a binary tree, balanced in an arbitrary way depending on how it happened to be constructed. In the 'darcs test' implementation it is used to wrap up a single patch or group of patches that might be the cause of a failure.

Constructors

Single :: p wX wY -> PatchSeq p wX wY 
Joined :: PatchSeq p wX wY -> PatchSeq p wY wZ -> PatchSeq p wX wZ 

Instances

Instances details
Apply p => Apply (PatchSeq p) Source # 
Instance details

Defined in Darcs.UI.Commands.Test.Impl

Associated Types

type ApplyState (PatchSeq p) :: (Type -> Type) -> Type Source #

Methods

apply :: ApplyMonad (ApplyState (PatchSeq p)) m => PatchSeq p wX wY -> m () Source #

unapply :: ApplyMonad (ApplyState (PatchSeq p)) m => PatchSeq p wX wY -> m () Source #

PatchInspect p => PatchInspect (PatchSeq p) Source # 
Instance details

Defined in Darcs.UI.Commands.Test.Impl

Show2 p => Show2 (PatchSeq p) Source # 
Instance details

Defined in Darcs.UI.Commands.Test.Impl

Methods

showDict2 :: ShowDict (PatchSeq p wX wY) Source #

Show2 p => Show1 (PatchSeq p wX) Source # 
Instance details

Defined in Darcs.UI.Commands.Test.Impl

Methods

showDict1 :: Dict (Show (PatchSeq p wX wX0)) Source #

Show2 p => Show (PatchSeq p wX wY) Source # 
Instance details

Defined in Darcs.UI.Commands.Test.Impl

Methods

showsPrec :: Int -> PatchSeq p wX wY -> ShowS #

show :: PatchSeq p wX wY -> String #

showList :: [PatchSeq p wX wY] -> ShowS #

type ApplyState (PatchSeq p) Source # 
Instance details

Defined in Darcs.UI.Commands.Test.Impl

patchTreeToFL :: PatchSeq p wX wY -> FL p wX wY Source #

type StrategyResult p wSuccess wFailure = StrategyResultRaw (PatchSeq p wSuccess wFailure) Source #

data StrategyResultRaw patches Source #

The result of running a test strategy.

Constructors

NoPasses

The chosen strategy didn't find any passing states in the repository.

NoFailureOnHead

The test didn't fail on head so there's no failure to track down.

Blame patches

The failure was tracked down to the given patches. these two are just for oneTest

RunSuccess

The single test run passed.

RunFailed Int

The single test run failed with the given exit code.

Instances

Instances details
Functor StrategyResultRaw Source # 
Instance details

Defined in Darcs.UI.Commands.Test.Impl

Show patches => Show (StrategyResultRaw patches) Source # 
Instance details

Defined in Darcs.UI.Commands.Test.Impl

Methods

showsPrec :: Int -> StrategyResultRaw patches -> ShowS #

show :: StrategyResultRaw patches -> String #

showList :: [StrategyResultRaw patches] -> ShowS #

Eq patches => Eq (StrategyResultRaw patches) Source # 
Instance details

Defined in Darcs.UI.Commands.Test.Impl

Methods

(==) :: StrategyResultRaw patches -> StrategyResultRaw patches -> Bool #

(/=) :: StrategyResultRaw patches -> StrategyResultRaw patches -> Bool #

runTestingEnv :: TestingParams -> TestingEnv m wA TestingDone a -> m a Source #

mkTestCmd :: (forall (wX :: *). IO (TestResult wX)) -> TestCmd Source #

runTestable :: (Commute p, TestRunner (TestingEnv m), TestRunnerPatchReqs (TestingEnv m) p) => SetScriptsExecutable -> TestCmd -> TestStrategy -> ShrinkFailure -> RL p wStart wA -> m (StrategyResultSealed p) Source #