diff options
author | Thomas Miedema <thomasmiedema@gmail.com> | 2016-04-25 16:58:34 +0200 |
---|---|---|
committer | Thomas Miedema <thomasmiedema@gmail.com> | 2016-04-26 10:50:05 +0200 |
commit | dadf82d61f3cced61e9ccc35a5219e0b32cfee9e (patch) | |
tree | 5cedbbc76fcb69f1dda1be2b131fd5be0c64f08c /testsuite/tests/programs | |
parent | e8c04d4ca5c78c6b68dab840ea53af42eee99364 (diff) | |
download | haskell-dadf82d61f3cced61e9ccc35a5219e0b32cfee9e.tar.gz |
Testsuite: fixup lots of tests
These aren't run very often, because they require external libraries.
https://ghc.haskell.org/trac/ghc/wiki/Building/RunningTests/Running#AdditionalPackages
maessen-hashtab still doesn't compile, QuickCheck api changed.
Update submodule hpc.
Diffstat (limited to 'testsuite/tests/programs')
-rw-r--r-- | testsuite/tests/programs/galois_raytrace/Eval.hs | 19 | ||||
-rw-r--r-- | testsuite/tests/programs/maessen-hashtab/HashTest.hs | 9 |
2 files changed, 18 insertions, 10 deletions
diff --git a/testsuite/tests/programs/galois_raytrace/Eval.hs b/testsuite/tests/programs/galois_raytrace/Eval.hs index 5939d4750b..bd9d419400 100644 --- a/testsuite/tests/programs/galois_raytrace/Eval.hs +++ b/testsuite/tests/programs/galois_raytrace/Eval.hs @@ -5,6 +5,7 @@ module Eval where +import Control.Monad import Data.Array import Geometry @@ -22,9 +23,16 @@ class Monad m => MonadEval m where newtype Pure a = Pure a deriving Show +instance Functor Pure where + fmap = liftM + +instance Applicative Pure where + pure = Pure + (<*>) = ap + instance Monad Pure where Pure x >>= k = k x - return = Pure + return = pure fail s = error s instance MonadEval Pure where @@ -286,11 +294,18 @@ newtype Abs a = Abs { runAbs :: Int -> AbsState a } data AbsState a = AbsState a !Int | AbsFail String +instance Functor Abs where + fmap = liftM + +instance Applicative Abs where + pure x = Abs (\ n -> AbsState x n) + (<*>) = ap + instance Monad Abs where (Abs fn) >>= k = Abs (\ s -> case fn s of AbsState r s' -> runAbs (k r) s' AbsFail m -> AbsFail m) - return x = Abs (\ n -> AbsState x n) + return = pure fail s = Abs (\ n -> AbsFail s) instance MonadEval Abs where diff --git a/testsuite/tests/programs/maessen-hashtab/HashTest.hs b/testsuite/tests/programs/maessen-hashtab/HashTest.hs index 51c60c0640..59795bb89e 100644 --- a/testsuite/tests/programs/maessen-hashtab/HashTest.hs +++ b/testsuite/tests/programs/maessen-hashtab/HashTest.hs @@ -34,7 +34,6 @@ instance Arbitrary Action where (5, liftM2 Insert arbitrary arbitrary), (3, liftM2 Update arbitrary arbitrary), (1, fmap Delete arbitrary)] - coarbitrary = error "coarbitrary Action" simA :: [Action] -> [Either Bool [Int]] simA = fst . foldl sim ([],[]) @@ -94,12 +93,10 @@ instance Show a => Show (List a) where instance Arbitrary HashFun where arbitrary = frequency [(20,return (HF hashInt)), (1,return (HF (const 0)))] - coarbitrary = error "coarbitrary HashFun" instance Arbitrary Empty where arbitrary = fmap mkE arbitrary where mkE (HF hf) = E {e = new (==) hf, hfe=HF hf} - coarbitrary = error "coarbitrary Empty" instance Arbitrary a => Arbitrary (List a) where arbitrary = do @@ -107,7 +104,6 @@ instance Arbitrary a => Arbitrary (List a) where (1,return (4096*2)), (0, return (1024*1024))] resize sz $ fmap L $ sized vector - coarbitrary = error "coarbitrary (List a)" instance Arbitrary MkH where arbitrary = do @@ -115,7 +111,6 @@ instance Arbitrary MkH where L list <- arbitrary let mkH act = H { h = act, hfh = hf } return (mkH . fromList (unHF hf) $ list) - coarbitrary = error "coarbitrary MkH" (==~) :: (Eq a) => IO a -> IO a -> Bool act1 ==~ act2 = unsafePerformIO act1 == unsafePerformIO act2 @@ -251,9 +246,7 @@ te :: (Testable a) => String -> a -> IO () -- te name prop = putStrLn name >> verboseCheck prop te name prop = do putStr name - check (defaultConfig{configMaxTest = 500, - configMaxFail = 10000, - configEvery = \_ _ -> "" }) prop + quickCheckWith stdArgs { maxSuccess = 500, maxSize = 10000 } prop main :: IO () main = do |