[Git][ghc/ghc][wip/T26268] testsuite: Add regression test for #26268

Ben Gamari pushed to branch wip/T26268 at Glasgow Haskell Compiler / GHC Commits: c0921e98 by Ben Gamari at 2025-08-11T23:30:32-04:00 testsuite: Add regression test for #26268 - - - - - 2 changed files: - + testsuite/tests/simplCore/should_compile/T24606.hs - testsuite/tests/simplCore/should_compile/all.T Changes: ===================================== testsuite/tests/simplCore/should_compile/T24606.hs ===================================== @@ -0,0 +1,27 @@ +{-# LANGUAGE CPP #-} + +-- | We expect 'liftA2' to inline into 'f1'. We test this by +-- grepping for occurrences of the 'Applicative' dictionary. +module RWST where + +import Data.Functor.Identity +import Control.Applicative +import Control.Monad + +newtype RWST r w s m a = RWST { runRWST :: r -> s -> m (w, s, a) } + +instance Functor m => Functor (RWST r w s m) where + fmap f (RWST m) = RWST (\r s -> fmap (\ ~(w,s',x) -> (w,s',f x)) (m r s)) + +instance (Monoid w, Monad m) => Applicative (RWST r w s m) where + pure x = RWST (\_ s -> pure (mempty, s, x)) + RWST mf <*> RWST mx = RWST (\r s -> do + ~(w, s', f) <- mf r s + ~(w', s'', x) <- mx r s' + pure (w <> w', s'', f x)) + +type Pairing m a b = m a -> m b -> m (a, b) + +f1 :: Pairing (RWST r [a] s Identity) a b +f1 x y = liftA2 (,) x y + ===================================== testsuite/tests/simplCore/should_compile/all.T ===================================== @@ -535,6 +535,7 @@ test('T25160', normal, compile, ['-O -ddump-rules']) test('T25197', [req_th, extra_files(["T25197_TH.hs"]), only_ways(['optasm'])], multimod_compile, ['T25197', '-O2 -v0']) test('T25389', normal, compile, ['-O -ddump-simpl -dsuppress-uniques -dno-typeable-binds']) test('T24359a', normal, compile, ['-O -ddump-rules']) +test('T24606', [grep_errmsg(r'fAlternativeRWST')], compile, ['-O -ddump-simpl -dsuppress-uniques -dsuppress-idinfo -dsuppress-coercions -dsuppress-coercion-types']) test('T25713', [grep_errmsg('W:::')], compile, ['-O -ddump-simpl']) test('T25883', normal, compile_grep_core, ['']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/c0921e98d726d4cd1e217b6306e6516d... -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/c0921e98d726d4cd1e217b6306e6516d... You're receiving this email because of your account on gitlab.haskell.org.
participants (1)
-
Ben Gamari (@bgamari)