
Simon Peyton Jones pushed to branch wip/T26315 at Glasgow Haskell Compiler / GHC Commits: 643d10bc by Simon Peyton Jones at 2025-09-10T08:46:08+01:00 Add a test case for #26396 ...same bug ast #26315 - - - - - 2 changed files: - + testsuite/tests/deriving/should_compile/T26396.hs - testsuite/tests/deriving/should_compile/all.T Changes: ===================================== testsuite/tests/deriving/should_compile/T26396.hs ===================================== @@ -0,0 +1,24 @@ +{-# LANGUAGE DataKinds #-} +{-# LANGUAGE GADTs #-} +{-# LANGUAGE QuantifiedConstraints #-} +{-# LANGUAGE UndecidableInstances #-} + +module T26396 where + +import Data.Kind +import Data.Type.Equality +import GHC.TypeNats + +newtype Vector (el :: Type) (len :: Natural) = Vector [el] + deriving (Eq) + +data Sized (f :: Natural -> Type) where + Sized :: KnownNat len => f len -> Sized f + +instance (forall (len :: Natural). Eq (f len)) => Eq (Sized f) where + Sized xs == Sized ys = case sameNat xs ys of + Nothing -> False + Just Refl -> xs == ys + +newtype Foo (el :: Type) = Foo (Sized (Vector el)) + deriving (Eq) ===================================== testsuite/tests/deriving/should_compile/all.T ===================================== @@ -154,3 +154,4 @@ test('T24955b', normal, compile, ['']) test('T24955c', normal, compile, ['']) test('T25148c', normal, compile, ['']) test('deriving-inferred-ty-arg', normal, compile, ['-ddump-deriv -dsuppress-uniques']) +test('T26396', normal, compile, ['']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/643d10bc437e8f2218129b007b659cf4... -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/643d10bc437e8f2218129b007b659cf4... You're receiving this email because of your account on gitlab.haskell.org.
participants (1)
-
Simon Peyton Jones (@simonpj)