Repository : ssh://darcs.haskell.org//srv/darcs/testsuite On branch : master
http://hackage.haskell.org/trac/ghc/changeset/9ad3ea3e6819f08da7e9744f832cce3bc8d880b8 >--------------------------------------------------------------- commit 9ad3ea3e6819f08da7e9744f832cce3bc8d880b8 Author: Simon Peyton Jones <[email protected]> Date: Fri Oct 12 13:59:07 2012 +0100 Test Trac #5751 >--------------------------------------------------------------- tests/typecheck/should_run/T5751.hs | 38 +++++++++++++++++++++++++++++++ tests/typecheck/should_run/T5751.stdout | 3 ++ tests/typecheck/should_run/all.T | 1 + 3 files changed, 42 insertions(+), 0 deletions(-) diff --git a/tests/typecheck/should_run/T5751.hs b/tests/typecheck/should_run/T5751.hs new file mode 100644 index 0000000..f620d8f --- /dev/null +++ b/tests/typecheck/should_run/T5751.hs @@ -0,0 +1,38 @@ +{-# LANGUAGE FlexibleContexts, FlexibleInstances, GeneralizedNewtypeDeriving, OverlappingInstances, UndecidableInstances #-} +module Main where + +class (Monad m) => MonadIO m where + -- | Lift a computation from the 'IO' monad. + liftIO :: IO a -> m a + +instance MonadIO IO where + liftIO = id + +class XMLGenerator m where + genElement :: (Maybe String, String) -> m () + +newtype IdentityT m a = IdentityT { runIdentityT :: m a } + deriving (Monad, MonadIO) + +instance (MonadIO m) => (XMLGenerator (IdentityT m)) where + genElement _ = liftIO $ putStrLn "in genElement" + +main :: IO () +main = + do runIdentityT web + putStrLn "done." + +class (Widgets x) => MonadRender x +class (XMLGenerator m) => Widgets m +-- instance Widgets (IdentityT IO) -- if you uncomment this, it will work +instance MonadRender m => Widgets m +instance MonadRender (IdentityT IO) + +web :: ( MonadIO m + , Widgets m + , XMLGenerator m + ) => m () +web = + do liftIO $ putStrLn "before" + genElement (Nothing, "p") + return () diff --git a/tests/typecheck/should_run/T5751.stdout b/tests/typecheck/should_run/T5751.stdout new file mode 100644 index 0000000..0686f3c --- /dev/null +++ b/tests/typecheck/should_run/T5751.stdout @@ -0,0 +1,3 @@ +before +in genElement +done. diff --git a/tests/typecheck/should_run/all.T b/tests/typecheck/should_run/all.T index 709bb32..ec1fcf6 100755 --- a/tests/typecheck/should_run/all.T +++ b/tests/typecheck/should_run/all.T @@ -97,3 +97,4 @@ test('T5573b', compose(omit_ways(['ghci']),only_compiler_types(['ghc'])), compil test('T7023', normal, compile_and_run, ['']) test('T7126', normal, compile_and_run, ['']) test('T6117', expect_broken(6117), compile_and_run, ['']) +test('T5751', normal, compile_and_run, ['']) _______________________________________________ Cvs-ghc mailing list [email protected] http://www.haskell.org/mailman/listinfo/cvs-ghc
