quickcheck-state-machine-0.7.1: Test monadic programs using state machine based models
Copyright(C) 2017 ATS Advanced Telematic Systems GmbH Li-yao Xia
LicenseBSD-style (see the file LICENSE)
MaintainerStevan Andjelkovic <stevan.andjelkovic@strath.ac.uk>
Stabilityprovisional
Portabilitynon-portable (GHC extensions)
Safe HaskellNone
LanguageHaskell2010

Test.StateMachine.Utils

Description

This module exports some QuickCheck utility functions. Some of these should perhaps be upstreamed.

Synopsis

Documentation

liftProperty :: Monad m => Property -> PropertyM m () Source #

Lifts a plain property into a monadic property.

whenFailM :: Monad m => IO () -> Property -> PropertyM m () Source #

anyP :: (a -> Property) -> [a] -> Property Source #

Lifts any to properties.

suchThatEither :: forall a. Gen a -> (a -> Bool) -> Gen (Either [a] a) Source #

data Shrunk a Source #

More permissive notion of shrinking where a value can shrink to itself

For example

shrink  3 == [0, 2] -- standard QuickCheck shrink
shrinkS 3 == [Shrunk True 0, Shrunk True 2, Shrunk False 3]

This is primarily useful when shrinking composite structures: the combinators here keep track of whether something was shrunk somewhere in the structure. For example, we have

   shrinkListS (shrinkPairS shrinkS shrinkS) [(1,3),(2,4)]
== [ Shrunk True  []             -- removed all elements of the list
   , Shrunk True  [(2,4)]        -- removed the first
   , Shrunk True  [(1,3)]        -- removed the second
   , Shrunk True  [(0,3),(2,4)]  -- shrinking the '1'
   , Shrunk True  [(1,0),(2,4)]  -- shrinking the '3'
   , Shrunk True  [(1,2),(2,4)]  -- ..
   , Shrunk True  [(1,3),(0,4)]  -- shrinking the '2'
   , Shrunk True  [(1,3),(1,4)]  -- ..
   , Shrunk True  [(1,3),(2,0)]  -- shrinking the '4'
   , Shrunk True  [(1,3),(2,2)]  -- ..
   , Shrunk True  [(1,3),(2,3)]  -- ..
   , Shrunk False [(1,3),(2,4)]  -- the original unchanged list
   ]

Constructors

Shrunk 

Fields

Instances

Instances details
Functor Shrunk Source # 
Instance details

Defined in Test.StateMachine.Utils

Methods

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

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

Eq a => Eq (Shrunk a) Source # 
Instance details

Defined in Test.StateMachine.Utils

Methods

(==) :: Shrunk a -> Shrunk a -> Bool #

(/=) :: Shrunk a -> Shrunk a -> Bool #

Show a => Show (Shrunk a) Source # 
Instance details

Defined in Test.StateMachine.Utils

Methods

showsPrec :: Int -> Shrunk a -> ShowS #

show :: Shrunk a -> String #

showList :: [Shrunk a] -> ShowS #

shrinkS :: Arbitrary a => a -> [Shrunk a] Source #

shrinkListS :: forall a. (a -> [Shrunk a]) -> [a] -> [Shrunk [a]] Source #

shrinkListS' :: [a] -> [Shrunk [a]] Source #

Shrink list without shrinking elements.

shrinkListS'' :: forall a. (a -> [Shrunk a]) -> [a] -> [Shrunk [a]] Source #

Shrink list by only shrinking elements.

shrinkPairS :: (a -> [Shrunk a]) -> (b -> [Shrunk b]) -> (a, b) -> [Shrunk (a, b)] Source #

shrinkPairS' :: (a -> [Shrunk a]) -> (a, a) -> [Shrunk (a, a)] Source #

pickOneReturnRest :: [a] -> [(a, [a])] Source #

pickOneReturnRest2 :: ([a], [a]) -> [(a, ([a], [a]))] Source #

pickOneReturnRestL :: [[a]] -> [(a, [[a]])] Source #

mkModel :: StateMachine model cmd m resp -> History cmd resp -> model Concrete Source #