[commit: ghc] master: Add testcase for T13818 (6cff2ca)
git at git.haskell.org
git at git.haskell.org
Tue Jul 11 17:42:35 UTC 2017
Repository : ssh://git@git.haskell.org/ghc
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/6cff2caddd9b329272a7d6965b20432e8078e0d8/ghc
>---------------------------------------------------------------
commit 6cff2caddd9b329272a7d6965b20432e8078e0d8
Author: Douglas Wilson <douglas.wilson at gmail.com>
Date: Tue Jul 11 11:55:15 2017 -0400
Add testcase for T13818
Annotations currently fail to type check if they annotation cannot
be loaded into ghci, such as when built with -fno-code.
Test Plan: ./validate
Reviewers: austin, bgamari
Reviewed By: bgamari
Subscribers: rwbarton, thomie
GHC Trac Issues: #13818
Differential Revision: https://phabricator.haskell.org/D3701
>---------------------------------------------------------------
6cff2caddd9b329272a7d6965b20432e8078e0d8
.../T4491 => annotations/should_compile/T13818}/A.hs | 7 +++----
.../T9562/B.hs-boot => annotations/should_compile/T13818/B.hs} | 2 +-
testsuite/tests/annotations/should_compile/T13818/all.T | 1 +
3 files changed, 5 insertions(+), 5 deletions(-)
diff --git a/testsuite/tests/quasiquotation/T4491/A.hs b/testsuite/tests/annotations/should_compile/T13818/A.hs
similarity index 62%
copy from testsuite/tests/quasiquotation/T4491/A.hs
copy to testsuite/tests/annotations/should_compile/T13818/A.hs
index dad3d03..1f04845 100644
--- a/testsuite/tests/quasiquotation/T4491/A.hs
+++ b/testsuite/tests/annotations/should_compile/T13818/A.hs
@@ -1,9 +1,8 @@
{-# LANGUAGE DeriveDataTypeable #-}
-
module A where
-import Data.Data
import Data.Typeable
+import Data.Data
-data Foo = Foo Int
- deriving (Show, Data, Typeable)
+data FromA = FromA
+ deriving (Typeable, Data)
diff --git a/testsuite/tests/driver/T9562/B.hs-boot b/testsuite/tests/annotations/should_compile/T13818/B.hs
similarity index 50%
copy from testsuite/tests/driver/T9562/B.hs-boot
copy to testsuite/tests/annotations/should_compile/T13818/B.hs
index facbc8c..d64afef 100644
--- a/testsuite/tests/driver/T9562/B.hs-boot
+++ b/testsuite/tests/annotations/should_compile/T13818/B.hs
@@ -2,4 +2,4 @@ module B where
import A
-oops :: F a b -> a -> b
+{-# ANN module FromA #-}
diff --git a/testsuite/tests/annotations/should_compile/T13818/all.T b/testsuite/tests/annotations/should_compile/T13818/all.T
new file mode 100644
index 0000000..ce858b6
--- /dev/null
+++ b/testsuite/tests/annotations/should_compile/T13818/all.T
@@ -0,0 +1 @@
+test('T13818', [expect_broken(13818),req_interp, omit_ways(prof_ways), extra_files(['A.hs', 'B.hs'])], multimod_compile, ['B', '-v0 -fno-code'])
\ No newline at end of file
More information about the ghc-commits
mailing list