
Simon Peyton Jones pushed to branch wip/T26176 at Glasgow Haskell Compiler / GHC Commits: 382c945f by Simon Peyton Jones at 2025-07-07T14:19:44+01:00 Add test for #14010 This test started to work in GHC 9.6 and has worked since. This MR just adds a regression test - - - - - 2 changed files: - + testsuite/tests/typecheck/should_compile/T14010.hs - testsuite/tests/typecheck/should_compile/all.T Changes: ===================================== testsuite/tests/typecheck/should_compile/T14010.hs ===================================== @@ -0,0 +1,44 @@ +{-# LANGUAGE NoImplicitPrelude, PolyKinds, DataKinds, TypeFamilies, + UndecidableSuperClasses, RankNTypes, TypeOperators, + FlexibleContexts, TypeSynonymInstances, FlexibleInstances, + UndecidableInstances #-} +module Monolith where + +import Data.Kind (Type) +import GHC.Exts (Constraint) + +type family (~>) :: c -> c -> Type + +type instance (~>) = (->) +type instance (~>) = ArrPair + +type family Fst (p :: (a, b)) :: a where + Fst '(x, _) = x + +type family Snd (p :: (a, b)) :: b where + Snd '(_, y) = y + +data ArrPair a b = ArrPair (Fst a ~> Fst b) (Snd a ~> Snd b) + +type family Super c :: Constraint where + Super Type = () + Super (c, d) = (Category c, Category d) + +class Super cat => Category cat where + id :: forall (a :: cat). a ~> a + +instance Category Type where + id = \x -> x + +instance (Category c, Category d) => Category (c, d) where + id = ArrPair id id + +-- The commented out version worked +-- class Category (c, d) => Functor (f :: c -> d) where +class (Category c, Category d) => Functor (f :: c -> d) where + map :: (a ~> b) -> (f a ~> f b) + +data OnSnd f a b = OnSnd (f '(a, b)) + +instance Functor (f :: (c, d) -> Type) => Functor (OnSnd f a) where + map f (OnSnd x) = OnSnd (map (ArrPair id f) x) ===================================== testsuite/tests/typecheck/should_compile/all.T ===================================== @@ -939,3 +939,4 @@ test('T25960', normal, compile, ['']) test('T26020', normal, compile, ['']) test('T26020a', [extra_files(['T26020a_help.hs'])], multimod_compile, ['T26020a', '-v0']) test('T25992', normal, compile, ['']) +test('T14010', normal, compile, ['']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/382c945ff0d3999aa92d52f1076ad331... -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/382c945ff0d3999aa92d52f1076ad331... You're receiving this email because of your account on gitlab.haskell.org.
participants (1)
-
Simon Peyton Jones (@simonpj)