[commit: testsuite] master: Test Trac #8011 (2d0d426)
Simon Peyton Jones
simonpj at microsoft.com
Tue Jun 25 15:14:47 CEST 2013
Repository : ssh://darcs.haskell.org//srv/darcs/testsuite
On branch : master
https://github.com/ghc/testsuite/commit/2d0d426af4d68b64b23262997fc34d0f22cc0008
>---------------------------------------------------------------
commit 2d0d426af4d68b64b23262997fc34d0f22cc0008
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date: Tue Jun 25 11:59:23 2013 +0100
Test Trac #8011
>---------------------------------------------------------------
tests/indexed-types/should_compile/Makefile | 5 +++++
tests/indexed-types/should_compile/T8011.hs | 9 +++++++++
tests/indexed-types/should_compile/T8011a.hs | 8 ++++++++
tests/indexed-types/should_compile/all.T | 6 ++++++
4 files changed, 28 insertions(+), 0 deletions(-)
diff --git a/tests/indexed-types/should_compile/Makefile b/tests/indexed-types/should_compile/Makefile
index 22710ed..c65d1f9 100644
--- a/tests/indexed-types/should_compile/Makefile
+++ b/tests/indexed-types/should_compile/Makefile
@@ -31,3 +31,8 @@ T8002:
'$(TEST_HC)' $(TEST_HC_OPTS) -c T8002b.hs
'$(TEST_HC)' $(TEST_HC_OPTS) -c T8002a.hs
'$(TEST_HC)' $(TEST_HC_OPTS) -c T8002.hs
+
+T8011:
+ $(RM) T8011a.o T8011a.hi T8011.o T8011.hi
+ '$(TEST_HC)' $(TEST_HC_OPTS) -c T8011a.hs
+ '$(TEST_HC)' $(TEST_HC_OPTS) -c T8011.hs
diff --git a/tests/indexed-types/should_compile/T8011.hs b/tests/indexed-types/should_compile/T8011.hs
new file mode 100644
index 0000000..8b27873
--- /dev/null
+++ b/tests/indexed-types/should_compile/T8011.hs
@@ -0,0 +1,9 @@
+{-# LANGUAGE FlexibleContexts #-}
+module T8011( clean ) where
+
+import Data.Char (isAlphaNum)
+import Data.List (dropWhile)
+import T8011a ( ToURL(URLT, toURL) )
+
+clean :: (ToURL url, Show (URLT url)) => url -> String
+clean = filter isAlphaNum . show . toURL
diff --git a/tests/indexed-types/should_compile/T8011a.hs b/tests/indexed-types/should_compile/T8011a.hs
new file mode 100644
index 0000000..d6b965f
--- /dev/null
+++ b/tests/indexed-types/should_compile/T8011a.hs
@@ -0,0 +1,8 @@
+{-# LANGUAGE TypeFamilies #-}
+module T8011a ( ToURL(toURL, nullURL, errorURL, URLT) ) where
+
+class ToURL a where
+ type URLT a
+ toURL :: a -> URLT a
+ nullURL :: a
+ errorURL :: a -> URLT a
diff --git a/tests/indexed-types/should_compile/all.T b/tests/indexed-types/should_compile/all.T
index 9575cf1..d81acef 100644
--- a/tests/indexed-types/should_compile/all.T
+++ b/tests/indexed-types/should_compile/all.T
@@ -219,3 +219,9 @@ test('T8002',
normal,
run_command,
['$MAKE -s --no-print-directory T8002'])
+
+# Import and export of associated types
+test('T8011',
+ normal,
+ run_command,
+ ['$MAKE -s --no-print-directory T8011'])
More information about the ghc-commits
mailing list