summaryrefslogtreecommitdiff
path: root/testsuite/tests/rebindable/rebindable9.hs
diff options
context:
space:
mode:
Diffstat (limited to 'testsuite/tests/rebindable/rebindable9.hs')
-rw-r--r--testsuite/tests/rebindable/rebindable9.hs43
1 files changed, 43 insertions, 0 deletions
diff --git a/testsuite/tests/rebindable/rebindable9.hs b/testsuite/tests/rebindable/rebindable9.hs
new file mode 100644
index 0000000000..081e22c46f
--- /dev/null
+++ b/testsuite/tests/rebindable/rebindable9.hs
@@ -0,0 +1,43 @@
+{-# LANGUAGE RebindableSyntax, FlexibleInstances,
+ MultiParamTypeClasses, FunctionalDependencies #-}
+
+-- Trac #1537
+
+module Foo where
+import qualified Prelude
+import Prelude hiding (Monad(..))
+
+newtype Identity a = Identity { runIdentity :: a }
+
+instance Prelude.Monad Identity where
+ return a = Identity a
+ m >>= k = k (runIdentity m)
+
+class Bind m1 m2 m3 | m1 m2 -> m3 where
+ (>>=) :: m1 a -> (a -> m2 b) -> m3 b
+
+class Return m where
+ returnM :: a -> m a
+ fail :: String -> m a
+
+instance Bind Maybe [] [] where
+ Just x >>= f = f x
+ Nothing >>= f = []
+
+instance Functor a => Bind Identity a a where m >>= f = f (runIdentity m)
+instance Functor a => Bind a Identity a where m >>= f = fmap (runIdentity . f) m
+
+instance Prelude.Monad m => Bind m m m where (>>=) = (Prelude.>>=)
+
+instance Return [] where
+ returnM x = [x]
+ fail _ = []
+
+return :: a -> Identity a
+return = Prelude.return
+
+should_compile :: [Int]
+should_compile = do
+ a <- Just 1
+ b <- [a*1,a*2]
+ return (b+1) \ No newline at end of file