[Git][ghc/ghc][wip/T25647] fix test T25647d

Patrick (@soulomoon) gitlab at gitlab.haskell.org
Mon Mar 10 19:31:36 UTC 2025



Patrick pushed to branch wip/T25647 at Glasgow Haskell Compiler / GHC


Commits:
7f973173 by Patrick at 2025-03-11T03:31:25+08:00
fix test T25647d

- - - - -


4 changed files:

- testsuite/tests/typecheck/should_compile/T25647d.hs
- + testsuite/tests/typecheck/should_compile/T25647d_fail.hs
- + testsuite/tests/typecheck/should_compile/T25647d_fail.stderr
- testsuite/tests/typecheck/should_compile/all.T


Changes:

=====================================
testsuite/tests/typecheck/should_compile/T25647d.hs
=====================================
@@ -15,14 +15,6 @@ type Cast1 :: forall (r :: RuntimeRep) (s :: RuntimeRep) (a :: RuntimeRep) (b ::
 type family Cast1 r s a b c d p where
   Cast1 _ c _ b Refl Refl (p->q) = Int
 
-type Cast2 :: forall (r :: RuntimeRep) (s :: RuntimeRep) (a :: RuntimeRep) (b :: RuntimeRep) -> (a :~: IntRep) -> (b :~: IntRep) -> Type -> Type
+type Cast2 :: forall (r :: RuntimeRep) (s :: RuntimeRep) (a :: RuntimeRep) (b :: RuntimeRep) -> (a :~: a) -> (b :~: b) -> Type -> Type
 type family Cast2 r s a b c d p where
-  Cast2 _ c _ b Refl Refl (p->q) = Int
-
-type Cast3 :: forall (r :: RuntimeRep) (s :: RuntimeRep) (a :: RuntimeRep) (b :: RuntimeRep) -> (a :~: IntRep) -> (b :~: IntRep) -> Type -> Type
-type family Cast3 r s a b c d p where
-  forall. Cast3 _ c _ b Refl Refl (p->q) = Int
-
-type Cast4 :: forall (r :: RuntimeRep) (s :: RuntimeRep) (a :: RuntimeRep) (b :: RuntimeRep) -> (a :~: IntRep) -> (b :~: IntRep) -> Type -> Type
-type family Cast4 r s a b c d p where
-  forall aa cc. Cast4 aa cc _ b Refl Refl (p->q) = Int
+  forall c b p q.Cast2 _ c _ b Refl Refl (p->q) = Int


=====================================
testsuite/tests/typecheck/should_compile/T25647d_fail.hs
=====================================
@@ -0,0 +1,16 @@
+{-# LANGUAGE DataKinds, TypeFamilies, PolyKinds, MagicHash #-}
+
+module T25647d_fail where
+
+import GHC.Exts
+import Data.Kind
+import GHC.Exts (RuntimeRep)
+import Data.Type.Equality ((:~:)(Refl) )
+
+type Cast3 :: forall (r :: RuntimeRep) (s :: RuntimeRep) (a :: RuntimeRep) (b :: RuntimeRep) -> (a :~: IntRep) -> (b :~: IntRep) -> Type -> Type
+type family Cast3 r s a b c d p where
+  forall. Cast3 _ c _ b Refl Refl (p->q) = Int
+
+type Cast4 :: forall (r :: RuntimeRep) (s :: RuntimeRep) (a :: RuntimeRep) (b :: RuntimeRep) -> (a :~: IntRep) -> (b :~: IntRep) -> Type -> Type
+type family Cast4 r s a b c d p where
+  forall aa cc b p q. Cast4 aa cc _ b Refl Refl (p->q) = Int


=====================================
testsuite/tests/typecheck/should_compile/T25647d_fail.stderr
=====================================
@@ -0,0 +1,12 @@
+T25647d_fail.hs:12:19: error: [GHC-76037]
+    Not in scope: type variable ‘c’
+
+T25647d_fail.hs:12:23: error: [GHC-76037]
+    Not in scope: type variable ‘b’
+
+T25647d_fail.hs:12:36: error: [GHC-76037]
+    Not in scope: type variable ‘p’
+
+T25647d_fail.hs:12:39: error: [GHC-76037]
+    Not in scope: type variable ‘q’
+


=====================================
testsuite/tests/typecheck/should_compile/all.T
=====================================
@@ -940,4 +940,5 @@ test('T25647b', normal, compile, [''])
 test('T25647c', normal, compile, [''])
 test('T25647d', normal, compile, [''])
 test('T25647_fail', normal, compile_fail, [''])
+test('T25647d_fail', normal, compile_fail, [''])
 test('T25725', normal, compile, [''])



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/7f97317308a441cb0a65c55140e767e685ac1ad4

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/7f97317308a441cb0a65c55140e767e685ac1ad4
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250310/d80f8d24/attachment-0001.html>


More information about the ghc-commits mailing list