-- $Header: c:/Source/Haskell/Wrapper/Data/Flex/QuickCheck/RCS/Wrap.hs,v 1.1 2011/06/04 00:46:28 dosuser Exp dosuser $ -- | QuickCheck tests for Data.Flex.Wrap module Data.Flex.QuickCheck.Wrap where import Test.QuickCheck import Data.Type.TList (TNil(..), (:*:)(..)) import Data.Flex.Wrap prop_defaultArbitrary_is_transparent i = forAll rand $ \g -> generate ai g wx == w (generate ai g x) where w = flexiWrap TNil {- N.B. The following circumlocution is necessary because fmap / liftM in the Gen monad split the PRNG -} x = fmap id arbitrary :: Gen Int wx = arbitrary ai = abs i prop_defaultCoarbitrary_is_transparent i a b = forAll rand $ \g -> generate ai g wx == generate ai g x where ai = abs i w = flexiWrap TNil x = coarbitrary a $ return b wx = coarbitrary (w a) $ return b types = (a :: Int, b :: Int) prop_transparentArbitrary_is_transparent i = forAll rand $ \g -> generate ai g wx == w (generate ai g x) where w = flexiWrap (FWTransparentArbitrary :*: TNil) {- N.B. The following circumlocution is necessary because fmap / liftM in the Gen monad split the PRNG -} x = fmap id arbitrary :: Gen Int wx = arbitrary ai = abs i prop_transparentCoarbitrary_is_transparent i a b = forAll rand $ \g -> generate ai g wx == generate ai g x where ai = abs i w = flexiWrap (FWTransparentArbitrary :*: TNil) x = coarbitrary a $ return b wx = coarbitrary (w a) $ return b types = (a :: Int, b :: Int) prop_explicitDefaultArbitrary_is_transparent i = forAll rand $ \g -> generate ai g wx == w (generate ai g x) where w = flexiWrap (FWDefaultArbitrary :*: TNil) {- N.B. The following circumlocution is necessary because fmap / liftM in the Gen monad split the PRNG -} x = fmap id arbitrary :: Gen Int wx = arbitrary ai = abs i prop_explicitDefaultCoarbitrary_is_transparent i a b = forAll rand $ \g -> generate ai g wx == generate ai g x where ai = abs i w = flexiWrap (FWDefaultArbitrary :*: TNil) x = coarbitrary a $ return b wx = coarbitrary (w a) $ return b types = (a :: Int, b :: Int) testArbitrary :: IO () testArbitrary = do quickCheck prop_defaultArbitrary_is_transparent quickCheck prop_defaultCoarbitrary_is_transparent quickCheck prop_transparentArbitrary_is_transparent quickCheck prop_transparentCoarbitrary_is_transparent quickCheck prop_explicitDefaultArbitrary_is_transparent quickCheck prop_explicitDefaultCoarbitrary_is_transparent -- vim: expandtab:tabstop=4:shiftwidth=4