[commit: ghc] master: Test #13938, with expect_broken (86e1db7)

git at git.haskell.org git at git.haskell.org
Thu Sep 14 19:36:11 UTC 2017


Repository : ssh://git@git.haskell.org/ghc

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/86e1db7d6850144d6e86dfb33eb0819205f6904c/ghc

>---------------------------------------------------------------

commit 86e1db7d6850144d6e86dfb33eb0819205f6904c
Author: Richard Eisenberg <rae at cs.brynmawr.edu>
Date:   Wed Aug 16 11:49:49 2017 -0400

    Test #13938, with expect_broken
    
    test case: dependent/should_compile/T13938


>---------------------------------------------------------------

86e1db7d6850144d6e86dfb33eb0819205f6904c
 testsuite/tests/dependent/should_compile/{T14038.hs => T13938.hs} | 7 ++++++-
 testsuite/tests/dependent/should_compile/all.T                    | 1 +
 2 files changed, 7 insertions(+), 1 deletion(-)

diff --git a/testsuite/tests/dependent/should_compile/T14038.hs b/testsuite/tests/dependent/should_compile/T13938.hs
similarity index 94%
copy from testsuite/tests/dependent/should_compile/T14038.hs
copy to testsuite/tests/dependent/should_compile/T13938.hs
index 839220a..3ba9e27 100644
--- a/testsuite/tests/dependent/should_compile/T14038.hs
+++ b/testsuite/tests/dependent/should_compile/T13938.hs
@@ -4,11 +4,12 @@
 {-# LANGUAGE GADTs #-}
 {-# LANGUAGE RankNTypes #-}
 {-# LANGUAGE ScopedTypeVariables #-}
+{-# LANGUAGE TemplateHaskell #-}
 {-# LANGUAGE TypeApplications #-}
 {-# LANGUAGE TypeFamilies #-}
 {-# LANGUAGE TypeInType #-}
 {-# LANGUAGE TypeOperators #-}
-module T14038 where
+module T13938 where
 
 import Data.Kind (Type)
 
@@ -39,12 +40,16 @@ type FunApp arr = (FunType arr, AppType arr)
 instance FunType (:->) where
   type Fun k1 (:->) k2 = k1 -> k2
 
+$(return []) -- This is only necessary for GHC 8.0 -- GHC 8.2 is smarter
+
 instance AppType (:->) where
   type App k1 (:->) k2 (f :: k1 -> k2) x = f x
 
 instance FunType (:~>) where
   type Fun k1 (:~>) k2 = k1 ~> k2
 
+$(return [])
+
 instance AppType (:~>) where
   type App k1 (:~>) k2 (f :: k1 ~> k2) x = f @@ x
 
diff --git a/testsuite/tests/dependent/should_compile/all.T b/testsuite/tests/dependent/should_compile/all.T
index bb21df7..684602c 100644
--- a/testsuite/tests/dependent/should_compile/all.T
+++ b/testsuite/tests/dependent/should_compile/all.T
@@ -28,3 +28,4 @@ test('T12176', normal, compile, [''])
 test('T14038', expect_broken(14038), compile, [''])
 test('T12742', normal, compile, [''])
 test('T13910', expect_broken(13910), compile, [''])
+test('T13938', expect_broken(13938), compile, [''])



More information about the ghc-commits mailing list