fitspec-0.4.7: refining property sets for testing Haskell programs

Copyright(c) 2015-2017 Rudy Matela
License3-Clause BSD (see the file LICENSE)
MaintainerRudy Matela <rudy@matela.com.br>
Safe HaskellNone
LanguageHaskell2010

Test.FitSpec.ShowMutable

Description

Exports a typeclass to show mutant variations.

Synopsis

Documentation

class ShowMutable a where Source #

Types that can have their mutation shown. Has only one function mutantS that returns a simple AST (MutantS) representing the mutant. A standard implementation of mutantS for Eq types is given by mutantSEq.

Minimal complete definition

mutantS

Methods

mutantS :: a -> a -> MutantS Source #

Instances
ShowMutable Bool Source # 
Instance details

Defined in Test.FitSpec.ShowMutable

Methods

mutantS :: Bool -> Bool -> MutantS Source #

ShowMutable Char Source # 
Instance details

Defined in Test.FitSpec.ShowMutable

Methods

mutantS :: Char -> Char -> MutantS Source #

ShowMutable Double Source # 
Instance details

Defined in Test.FitSpec.ShowMutable

ShowMutable Float Source # 
Instance details

Defined in Test.FitSpec.ShowMutable

Methods

mutantS :: Float -> Float -> MutantS Source #

ShowMutable Int Source # 
Instance details

Defined in Test.FitSpec.ShowMutable

Methods

mutantS :: Int -> Int -> MutantS Source #

ShowMutable Integer Source # 
Instance details

Defined in Test.FitSpec.ShowMutable

ShowMutable Ordering Source # 
Instance details

Defined in Test.FitSpec.ShowMutable

ShowMutable Word Source # 
Instance details

Defined in Test.FitSpec.ShowMutable

Methods

mutantS :: Word -> Word -> MutantS Source #

ShowMutable () Source # 
Instance details

Defined in Test.FitSpec.ShowMutable

Methods

mutantS :: () -> () -> MutantS Source #

ShowMutable Int1 Source # 
Instance details

Defined in Test.FitSpec.TestTypes

Methods

mutantS :: Int1 -> Int1 -> MutantS Source #

ShowMutable Int2 Source # 
Instance details

Defined in Test.FitSpec.TestTypes

Methods

mutantS :: Int2 -> Int2 -> MutantS Source #

ShowMutable Int3 Source # 
Instance details

Defined in Test.FitSpec.TestTypes

Methods

mutantS :: Int3 -> Int3 -> MutantS Source #

ShowMutable Int4 Source # 
Instance details

Defined in Test.FitSpec.TestTypes

Methods

mutantS :: Int4 -> Int4 -> MutantS Source #

ShowMutable Word1 Source # 
Instance details

Defined in Test.FitSpec.TestTypes

Methods

mutantS :: Word1 -> Word1 -> MutantS Source #

ShowMutable Word2 Source # 
Instance details

Defined in Test.FitSpec.TestTypes

Methods

mutantS :: Word2 -> Word2 -> MutantS Source #

ShowMutable Word3 Source # 
Instance details

Defined in Test.FitSpec.TestTypes

Methods

mutantS :: Word3 -> Word3 -> MutantS Source #

ShowMutable Word4 Source # 
Instance details

Defined in Test.FitSpec.TestTypes

Methods

mutantS :: Word4 -> Word4 -> MutantS Source #

ShowMutable Nat Source # 
Instance details

Defined in Test.FitSpec.TestTypes

Methods

mutantS :: Nat -> Nat -> MutantS Source #

(Eq a, Show a) => ShowMutable [a] Source # 
Instance details

Defined in Test.FitSpec.ShowMutable

Methods

mutantS :: [a] -> [a] -> MutantS Source #

(Eq a, Show a) => ShowMutable (Maybe a) Source # 
Instance details

Defined in Test.FitSpec.ShowMutable

Methods

mutantS :: Maybe a -> Maybe a -> MutantS Source #

(Eq a, Show a, Integral a) => ShowMutable (Ratio a) Source # 
Instance details

Defined in Test.FitSpec.ShowMutable

Methods

mutantS :: Ratio a -> Ratio a -> MutantS Source #

(Listable a, Show a, ShowMutable b) => ShowMutable (a -> b) Source # 
Instance details

Defined in Test.FitSpec.ShowMutable

Methods

mutantS :: (a -> b) -> (a -> b) -> MutantS Source #

(Eq a, Show a, Eq b, Show b) => ShowMutable (Either a b) Source # 
Instance details

Defined in Test.FitSpec.ShowMutable

Methods

mutantS :: Either a b -> Either a b -> MutantS Source #

(ShowMutable a, ShowMutable b) => ShowMutable (a, b) Source # 
Instance details

Defined in Test.FitSpec.ShowMutable

Methods

mutantS :: (a, b) -> (a, b) -> MutantS Source #

(ShowMutable a, ShowMutable b, ShowMutable c) => ShowMutable (a, b, c) Source # 
Instance details

Defined in Test.FitSpec.ShowMutable

Methods

mutantS :: (a, b, c) -> (a, b, c) -> MutantS Source #

(ShowMutable a, ShowMutable b, ShowMutable c, ShowMutable d) => ShowMutable (a, b, c, d) Source # 
Instance details

Defined in Test.FitSpec.ShowMutable

Methods

mutantS :: (a, b, c, d) -> (a, b, c, d) -> MutantS Source #

(ShowMutable a, ShowMutable b, ShowMutable c, ShowMutable d, ShowMutable e) => ShowMutable (a, b, c, d, e) Source # 
Instance details

Defined in Test.FitSpec.ShowMutable

Methods

mutantS :: (a, b, c, d, e) -> (a, b, c, d, e) -> MutantS Source #

(ShowMutable a, ShowMutable b, ShowMutable c, ShowMutable d, ShowMutable e, ShowMutable f) => ShowMutable (a, b, c, d, e, f) Source # 
Instance details

Defined in Test.FitSpec.ShowMutable

Methods

mutantS :: (a, b, c, d, e, f) -> (a, b, c, d, e, f) -> MutantS Source #

(ShowMutable a, ShowMutable b, ShowMutable c, ShowMutable d, ShowMutable e, ShowMutable f, ShowMutable g) => ShowMutable (a, b, c, d, e, f, g) Source # 
Instance details

Defined in Test.FitSpec.ShowMutable.Tuples

Methods

mutantS :: (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) -> MutantS Source #

(ShowMutable a, ShowMutable b, ShowMutable c, ShowMutable d, ShowMutable e, ShowMutable f, ShowMutable g, ShowMutable h) => ShowMutable (a, b, c, d, e, f, g, h) Source # 
Instance details

Defined in Test.FitSpec.ShowMutable.Tuples

Methods

mutantS :: (a, b, c, d, e, f, g, h) -> (a, b, c, d, e, f, g, h) -> MutantS Source #

(ShowMutable a, ShowMutable b, ShowMutable c, ShowMutable d, ShowMutable e, ShowMutable f, ShowMutable g, ShowMutable h, ShowMutable i) => ShowMutable (a, b, c, d, e, f, g, h, i) Source # 
Instance details

Defined in Test.FitSpec.ShowMutable.Tuples

Methods

mutantS :: (a, b, c, d, e, f, g, h, i) -> (a, b, c, d, e, f, g, h, i) -> MutantS Source #

(ShowMutable a, ShowMutable b, ShowMutable c, ShowMutable d, ShowMutable e, ShowMutable f, ShowMutable g, ShowMutable h, ShowMutable i, ShowMutable j) => ShowMutable (a, b, c, d, e, f, h, g, i, j) Source # 
Instance details

Defined in Test.FitSpec.ShowMutable.Tuples

Methods

mutantS :: (a, b, c, d, e, f, h, g, i, j) -> (a, b, c, d, e, f, h, g, i, j) -> MutantS Source #

(ShowMutable a, ShowMutable b, ShowMutable c, ShowMutable d, ShowMutable e, ShowMutable f, ShowMutable g, ShowMutable h, ShowMutable i, ShowMutable j, ShowMutable k) => ShowMutable (a, b, c, d, e, f, g, h, i, j, k) Source # 
Instance details

Defined in Test.FitSpec.ShowMutable.Tuples

Methods

mutantS :: (a, b, c, d, e, f, g, h, i, j, k) -> (a, b, c, d, e, f, g, h, i, j, k) -> MutantS Source #

(ShowMutable a, ShowMutable b, ShowMutable c, ShowMutable d, ShowMutable e, ShowMutable f, ShowMutable g, ShowMutable h, ShowMutable i, ShowMutable j, ShowMutable k, ShowMutable l) => ShowMutable (a, b, c, d, e, f, g, h, i, j, k, l) Source # 
Instance details

Defined in Test.FitSpec.ShowMutable.Tuples

Methods

mutantS :: (a, b, c, d, e, f, g, h, i, j, k, l) -> (a, b, c, d, e, f, g, h, i, j, k, l) -> MutantS Source #

mutantSEq :: (Eq a, Show a) => a -> a -> MutantS Source #

For a given type Type instance of Eq and Show, define the ShowMutable instance as:

instance ShowMutable Type
  where mutantS = mutantSEq

showMutantAsTuple :: ShowMutable a => [String] -> a -> a -> String Source #

Show a Mutant as a tuple of lambdas.

> putStrLn $ showMutantAsTuple ["p && q","not p"] ((&&),not) ((||),id)
( \p q -> case (p,q) of
           (False,False) -> True
           _ -> p && q
, \p -> case p of
          False -> False
          True -> True
          _ -> not p )

Can be easily copy pasted into an interactive session for manipulation. On GHCi, use :{ and :} to allow multi-line expressions and definitions.

showMutantNested :: ShowMutable a => [String] -> a -> a -> String Source #

Show a Mutant as a tuple of nested lambdas. Very similar to showMutantAsTuple, but the underlying data structure is not flatten: so the output is as close as possible to the underlying representation.

showMutantDefinition :: ShowMutable a => [String] -> a -> a -> String Source #

Show a Mutant as a new complete top-level definition, with a prime appended to the name of the mutant.

> putStrLn $ showMutantDefinition ["p && q","not p"] ((&&),not) ((==),id)
False &&- False = True
p     &&- q     = p && q
not' False = False
not' True  = True
not' p     = not p

showMutantBindings :: ShowMutable a => [String] -> a -> a -> String Source #

Show a Mutant as the list of bindings that differ from the original function(s).

> putStrLn $ showMutantBindings ["p && q","not p"] ((&&),not) ((==),id)
False && False = True
not False = False
not True  = True

Can possibly be copied into the source of the original function for manipulation.

data MutantS Source #

(Show) Structure of a mutant. This format is intended for processing then pretty-printing.

Instances
Show MutantS Source # 
Instance details

Defined in Test.FitSpec.ShowMutable