diff options
author | sheaf <sam.derbyshire@gmail.com> | 2022-03-31 12:40:36 +0200 |
---|---|---|
committer | Jakob Bruenker <jakob.bruenker@gmail.com> | 2022-04-01 20:33:05 +0200 |
commit | c6f77f3912a9178cf839a14c3d6ed590820d18ed (patch) | |
tree | 995206548c08f8dac4f8fd56a54c89e03527db13 /testsuite | |
parent | 32070e6c2e1b4b7c32530a9566fe14543791f9a6 (diff) | |
download | haskell-c6f77f3912a9178cf839a14c3d6ed590820d18ed.tar.gz |
Add a regression test for #21323
This bug was fixed at some point between GHC 9.0 and GHC 9.2;
this patch simply adds a regression test.
Diffstat (limited to 'testsuite')
-rw-r--r-- | testsuite/tests/typecheck/should_compile/T21323.hs | 55 | ||||
-rw-r--r-- | testsuite/tests/typecheck/should_compile/all.T | 1 |
2 files changed, 56 insertions, 0 deletions
diff --git a/testsuite/tests/typecheck/should_compile/T21323.hs b/testsuite/tests/typecheck/should_compile/T21323.hs new file mode 100644 index 0000000000..aa7d07da91 --- /dev/null +++ b/testsuite/tests/typecheck/should_compile/T21323.hs @@ -0,0 +1,55 @@ +{-# Language ConstraintKinds #-} +{-# Language FlexibleContexts #-} +{-# Language FlexibleInstances #-} +{-# Language GADTs #-} +{-# Language ImpredicativeTypes #-} +{-# Language InstanceSigs #-} +{-# Language MultiParamTypeClasses #-} +{-# Language PolyKinds #-} +{-# Language PolyKinds #-} +{-# Language PolyKinds #-} +{-# Language QuantifiedConstraints #-} +{-# Language ScopedTypeVariables #-} +{-# Language StandaloneKindSignatures #-} +{-# Language TypeApplications #-} +{-# Language TypeFamilies #-} + +module T21323 where + +import Data.Kind +import Data.Coerce +import Data.Type.Coercion +import GHC.Generics + +data Dict cls where + Dict :: cls => Dict cls + +type ViaRep :: Type -> (k -> Type) -> Type +newtype a `ViaRep` rep = ViaRep a + +class Coercible (Rep a x) (rep x) => AuxCoercible a rep x +instance Coercible (Rep a x) (rep x) => AuxCoercible a rep x + +type ForallAuxCoercible a rep = forall x. AuxCoercible a rep x + +instance (Generic a, ForallAuxCoercible a rep) => Generic (ViaRep a rep) where + type Rep (ViaRep a rep) = rep + + from :: forall x. ViaRep a rep -> rep x + from (ViaRep a) = co undefined (from @a @x a) where -- coerce (from @a @x a) where + + co :: Coercion (Rep a x) (rep x) -> Rep a x -> rep x + co = undefined + + c :: Dict (ForallAuxCoercible a rep) + c = Dict + +-- This caused a Core Lint error on GHC 9.0: +-- +-- Out of scope: irred_a1LI :: cls_a1LH[tau:3] +-- [LclId] +-- In the RHS of $cfrom_a1KZ :: forall a (rep :: * -> *) x. +-- (Generic a, ForallAuxCoercible a rep) => +-- ViaRep a rep -> Rep (ViaRep a rep) x + + to = undefined diff --git a/testsuite/tests/typecheck/should_compile/all.T b/testsuite/tests/typecheck/should_compile/all.T index f7b6cb82e7..a503d60b7c 100644 --- a/testsuite/tests/typecheck/should_compile/all.T +++ b/testsuite/tests/typecheck/should_compile/all.T @@ -822,3 +822,4 @@ test('T18406b', normal, compile, ['-ddump-tc -fprint-explicit-foralls -dsuppress test('T18529', normal, compile, ['-ddump-tc -fprint-explicit-foralls -dsuppress-uniques -fprint-typechecker-elaboration']) test('T21023', normal, compile, ['-ddump-types']) test('T21205', normal, compile, ['-O0']) +test('T21323', normal, compile, ['']) |