[commit: testsuite] master: Test Trac #4185 (c4ea06f)
Simon Peyton Jones
simonpj at microsoft.com
Thu May 30 15:07:20 CEST 2013
Repository : ssh://darcs.haskell.org//srv/darcs/testsuite
On branch : master
https://github.com/ghc/testsuite/commit/c4ea06f46f6ee8808263ed5d5647ced4df1b3999
>---------------------------------------------------------------
commit c4ea06f46f6ee8808263ed5d5647ced4df1b3999
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date: Thu May 30 14:01:29 2013 +0100
Test Trac #4185
>---------------------------------------------------------------
tests/indexed-types/should_compile/T4185.hs | 46 +++++++++++++++++++++++++++
tests/indexed-types/should_compile/all.T | 1 +
2 files changed, 47 insertions(+), 0 deletions(-)
diff --git a/tests/indexed-types/should_compile/T4185.hs b/tests/indexed-types/should_compile/T4185.hs
new file mode 100644
index 0000000..6a1be25
--- /dev/null
+++ b/tests/indexed-types/should_compile/T4185.hs
@@ -0,0 +1,46 @@
+{-# LANGUAGE DeriveFunctor, StandaloneDeriving, FlexibleInstances, TypeFamilies, GeneralizedNewtypeDeriving #-}
+module T4185 where
+
+data family Foo k :: * -> *
+
+------------- Generalised newtype deriving of user class -----------
+class Bar f where
+ bar :: f a -> Int
+ woo :: f a -> f a
+
+instance Bar Maybe where
+ bar Nothing = 0
+ bar Just{} = 1
+ woo x = x
+
+-- Deriving clause
+newtype instance Foo Int a = FooInt (Maybe a) deriving (Bar)
+
+-- Standalone deriving
+newtype instance Foo Char a = FooChar (Maybe a)
+deriving instance Bar (Foo Char)
+
+{-
+dBarMaybe :: Bar Maybe
+
+newtype FooInt a = FooInt (Maybe a)
+axiom ax7 a : Foo Int a ~ FooInt a -- Family axiom
+axiom ax7 : FooInt ~ Maybe -- Newtype axiom
+
+dBarFooInt :: Bar (Foo Int)
+dBarFooInt = dBarMaybe |> Bar ax7
+-}
+
+------------- Deriving on data types for Functor -----------
+
+-- Deriving clause
+data instance Foo Bool a = FB1 a | FB2 a deriving( Functor )
+
+-- Standalone deriving
+data instance Foo Float a = FB3 a
+deriving instance Functor (Foo Float)
+
+
+--instance Functor (Foo Bool) where
+-- fmap f (FB1 x) = FB1 (f x)
+-- fmap f (FB2 y) = FB2 (f y)
\ No newline at end of file
diff --git a/tests/indexed-types/should_compile/all.T b/tests/indexed-types/should_compile/all.T
index 15e9877..cc6b21a 100644
--- a/tests/indexed-types/should_compile/all.T
+++ b/tests/indexed-types/should_compile/all.T
@@ -210,4 +210,5 @@ test('T7585', normal, compile, [''])
test('T7282', normal, compile, [''])
test('T7804', normal, compile, [''])
test('T7837', normal, compile, ['-O -ddump-rule-firings'])
+test('T4185', normal, compile, [''])
More information about the ghc-commits
mailing list