MuCheck-0.3.0.4: Automated Mutation Testing

Safe HaskellNone
LanguageHaskell2010

Test.MuCheck.Mutation

Description

This module handles the mutation of different patterns.

Synopsis

Documentation

genMutants Source

Arguments

:: String

The mutating function under test

-> FilePath

The module where the mutating function is declared

-> IO [Mutant]

Returns the mutants produced.

The genMutants function is a wrapper to genMutantsWith with standard configuraton

genMutantsWith Source

Arguments

:: Config

The configuration to be used

-> String

The mutating function

-> FilePath

The module file where mutating function was declared

-> IO [Mutant]

Returns the mutants produced

The genMutantsWith function takes configuration function to mutate, function to mutate, filename the function is defined in, and produces mutants in the same directory as the filename, and returns the number of mutants produced.

sampler Source

Arguments

:: RandomGen g 
=> Config

Configuration

-> g

The random seed

-> MuVars

What kind of a mutation are we interested in?

-> [t]

The original list of mutation operators

-> [t]

Returns the sampled mutation operators

Wrapper around sampleF that returns correct sampling ratios according to configuration passed.

genMutantsForSrc Source

Arguments

:: Config

Configuration

-> String

The mutating function

-> String

The module where mutating function was declared

-> (MuVars -> [MuOp] -> [MuOp])

The sampling function

-> [Mutant]

Returns the sampled mutants

The genMutantsForSrc takes the function name to mutate, source where it is defined, and a sampling function, and returns the mutated sources selected using sampling function.

replaceDef :: Decl -> Decl -> Module -> [Decl] Source

Replace old function definition with a new one in the AST

getFunc :: String -> Module -> Decl Source

Fetch the function definition from module

mutates :: [MuOp] -> Decl -> [Decl] Source

Higher order mutation of a function's code using a bunch of mutation operators (In all the three mutate functions, we assume working with functions declaration.)

mutatesN :: [MuOp] -> Decl -> Int -> [Decl] Source

First and higher order mutation. The third argument specifies whether it's first order or higher order

mutate :: MuOp -> Decl -> [Decl] Source

Given a function, generate all mutants after applying applying op once (op might be applied at different places). E.g.: if the operator is (op = "== ">") and there are two instances of "<" in the AST, then it will return two AST with each replaced.

isFunctionD :: String -> Decl -> Bool Source

is the parsed expression the function we are looking for?

permMatches :: Decl -> [MuOp] Source

Generate all operators for permutating pattern matches in a function. We don't deal with permutating guards and case for now.

removeOnePMatch :: Decl -> [MuOp] Source

Generates transformations that removes one pattern match from a function definition.

removeOneElem :: Eq t => [t] -> [[t]] Source

Generate sub-arrays with one less element

getASTFromStr :: String -> Module Source

Returns the AST from the file

putDecls :: Module -> [Decl] -> Module Source

Set the declaration in a module

selectValOps :: (Typeable b, Mutable b) => (b -> Bool) -> (b -> [b]) -> Decl -> [MuOp] Source

For valops, unlike functions, we specify how any given literal value might change. So we take a predicate specifying how to recognize the literal value, a list of mappings specifying how the literal can change, and the AST, and recurse over the AST looking for literals that match our predicate. When we find any, we apply the given list of mappings to them, and produce a MuOp mapping between the original value and transformed value. This list of MuOp mappings are then returned.

selectLitOps :: Decl -> [MuOp] Source

Look for literal values in AST, and return applicable MuOp transforms. Unfortunately booleans are not handled here.

selectBLitOps :: Decl -> [MuOp] Source

Convert Boolean Literals

(True, False)

becomes

(False, True)

selectIfElseBoolNegOps :: Decl -> [MuOp] Source

Negating boolean in if/else statements

if True then 1 else 0

becomes

if True then 0 else 1

selectGuardedBoolNegOps :: Decl -> [MuOp] Source

Negating boolean in Guards | negate guarded booleans in guarded definitions

myFn x | x == 1 = True
myFn   | otherwise = False

becomes

myFn x | not (x == 1) = True
myFn   | otherwise = False