[commit: ghc] wip/dph-fix: Make Applicative-Monad fixes for tests. (daf3c22)
git at git.haskell.org
git at git.haskell.org
Thu Oct 2 21:44:21 UTC 2014
Repository : ssh://git@git.haskell.org/ghc
On branch : wip/dph-fix
Link : http://ghc.haskell.org/trac/ghc/changeset/daf3c2255a2aa7661937648e2f42fd1e8f64f8df/ghc
>---------------------------------------------------------------
commit daf3c2255a2aa7661937648e2f42fd1e8f64f8df
Author: Geoffrey Mainland <mainland at cs.drexel.edu>
Date: Thu Oct 2 17:39:34 2014 -0400
Make Applicative-Monad fixes for tests.
>---------------------------------------------------------------
daf3c2255a2aa7661937648e2f42fd1e8f64f8df
testsuite/tests/array/should_run/arr016.hs | 8 ++++++--
testsuite/tests/codeGen/should_run/CopySmallArrayStressTest.hs | 2 +-
testsuite/tests/codeGen/should_run/cgrun068.hs | 2 +-
3 files changed, 8 insertions(+), 4 deletions(-)
diff --git a/testsuite/tests/array/should_run/arr016.hs b/testsuite/tests/array/should_run/arr016.hs
index 055e660..0e8e2bf 100644
--- a/testsuite/tests/array/should_run/arr016.hs
+++ b/testsuite/tests/array/should_run/arr016.hs
@@ -1,4 +1,4 @@
-{-# LANGUAGE ScopedTypeVariables, DatatypeContexts #-}
+{-# LANGUAGE ScopedTypeVariables #-}
module Main where
@@ -151,7 +151,7 @@ instance Show (a -> b) where { show _ = "<FN>" }
------------------------------------------------------------------------------
-data (Ix a) => Array a b = MkArray (a,a) (a -> b) deriving ()
+data Array a b = MkArray (a,a) (a -> b) deriving ()
array :: (Ix a) => (a,a) -> [(a,b)] -> Array a b
array b ivs =
@@ -259,6 +259,10 @@ generate n rnd (Gen m) = m size rnd'
instance Functor Gen where
fmap f m = m >>= return . f
+instance Applicative Gen where
+ pure = return
+ (<*>) = liftM2 id
+
instance Monad Gen where
return a = Gen (\n r -> a)
Gen m >>= k =
diff --git a/testsuite/tests/codeGen/should_run/CopySmallArrayStressTest.hs b/testsuite/tests/codeGen/should_run/CopySmallArrayStressTest.hs
index 7243fad..05a84df 100644
--- a/testsuite/tests/codeGen/should_run/CopySmallArrayStressTest.hs
+++ b/testsuite/tests/codeGen/should_run/CopySmallArrayStressTest.hs
@@ -361,7 +361,7 @@ cloneMArraySlow !marr !off n =
-- Utilities for simplifying RNG passing
newtype Rng s a = Rng { unRng :: StateT StdGen (ST s) a }
- deriving Monad
+ deriving (Functor, Applicative, Monad)
-- Same as 'randomR', but using the RNG state kept in the 'Rng' monad.
rnd :: Random a => (a, a) -> Rng s a
diff --git a/testsuite/tests/codeGen/should_run/cgrun068.hs b/testsuite/tests/codeGen/should_run/cgrun068.hs
index 69a8b27..00d1249 100644
--- a/testsuite/tests/codeGen/should_run/cgrun068.hs
+++ b/testsuite/tests/codeGen/should_run/cgrun068.hs
@@ -361,7 +361,7 @@ cloneMArraySlow !marr !off n =
-- Utilities for simplifying RNG passing
newtype Rng s a = Rng { unRng :: StateT StdGen (ST s) a }
- deriving Monad
+ deriving (Functor, Applicative, Monad)
-- Same as 'randomR', but using the RNG state kept in the 'Rng' monad.
rnd :: Random a => (a, a) -> Rng s a
More information about the ghc-commits
mailing list