[GHC] #14045: Data family instances must list all patterns of family, despite documentation's claims to the contrary
GHC
ghc-devs at haskell.org
Wed Aug 2 16:13:54 UTC 2017
#14045: Data family instances must list all patterns of family, despite
documentation's claims to the contrary
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler (Type | Version: 8.3
checker) |
Resolution: | Keywords: TypeFamilies
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: GHC rejects | Test Case: indexed-
valid program | types/should_compile/T14045,
| indexed-types/should_fail/T14045a
Blocked By: | Blocking:
Related Tickets: #12369 | Differential Rev(s): Phab:D3804
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by simonpj):
I ran out of time, got stuck upgrading to GHC 8 which is now required...
Here is the patch: Ryan, would you like to validate and commit?
{{{
simonpj at cam-05-unx:~/code/HEAD$ git show 143f08a3
commit 143f08a32b80f7f80d77b518ce207a1051368b9e
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date: Wed Aug 2 15:57:21 2017 +0100
Get the roles right for newtype instances
This was a simple slip, that gave rise to the bug reported in
comment:13 of Trac #14045. We were supplying roles to mkAlgTyCon
that didn't match the tyvars.
diff --git a/compiler/typecheck/TcInstDcls.hs
b/compiler/typecheck/TcInstDcls.hs
index fe513f4..58d4506 100644
--- a/compiler/typecheck/TcInstDcls.hs
+++ b/compiler/typecheck/TcInstDcls.hs
@@ -695,7 +695,7 @@ tcDataFamInstDecl mb_clsinfo
-- the end of Note [Data type families] in TyCon
rep_tc = mkAlgTyCon rep_tc_name
ty_binders liftedTypeKind
- (map (const Nominal) full_tvs)
+ (map (const Nominal)
ty_binders)
(fmap unLoc cType) stupid_theta
tc_rhs parent
gadt_syntax
diff --git a/compiler/types/Type.hs b/compiler/types/Type.hs
index b81192f..dcc134c 100644
--- a/compiler/types/Type.hs
+++ b/compiler/types/Type.hs
@@ -1315,8 +1315,12 @@ mkLamType v ty
mkLamTypes vs ty = foldr mkLamType ty vs
--- | Given a list of type-level vars and a result type, makes TyBinders,
preferring
--- anonymous binders if the variable is, in fact, not dependent.
+-- | Given a list of type-level vars and a result kind,
+-- makes TyBinders, preferring anonymous binders
+-- if the variable is, in fact, not dependent.
+-- e.g. mkTyConBindersPreferAnon [(k:*),(b:k),(c:k)] (k->k)
+-- We want (k:*) Named, (a;k) Anon, (c:k) Anon
+--
-- All binders are /visible/.
mkTyConBindersPreferAnon :: [TyVar] -> Type -> [TyConBinder]
mkTyConBindersPreferAnon vars inner_ty = fst (go vars)
diff --git a/testsuite/tests/deriving/should_compile/T14045.hs
b/testsuite/tests/deriving/should_compile/T14045.hs
new file mode 100644
index 0000000..d721a3d
--- /dev/null
+++ b/testsuite/tests/deriving/should_compile/T14045.hs
@@ -0,0 +1,13 @@
+{-# LANGUAGE TypeFamilies, KindSignatures, GADTs,
GeneralizedNewtypeDeriving #-}
+
+module T14045 where
+
+import Data.Kind ( Type )
+
+data family T a b :: Type
+
+-- newtype instance T Int d = MkT (IO d)
+
+newtype instance T Int :: Type -> Type where
+ MkT :: IO d -> T Int d
+ deriving( Monad, Applicative, Functor )
diff --git a/testsuite/tests/deriving/should_compile/all.T
b/testsuite/tests/deriving/should_compile/all.T
index 0025d25..10e2e60 100644
--- a/testsuite/tests/deriving/should_compile/all.T
+++ b/testsuite/tests/deriving/should_compile/all.T
@@ -94,3 +94,4 @@ test('drv-phantom',
[normalise_errmsg_fun(just_the_deriving)],compile, ['-ddump-
test('T13813', normal, compile, [''])
test('T13919', normal, compile, [''])
test('T13998', normal, compile, [''])
+test('T14045', normal, compile, [''])
}}}
Thanks!
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/14045#comment:16>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list