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
2 changed files:
Changes:
1 | +{-# LANGUAGE CPP #-}
|
|
2 | + |
|
3 | +-- | We expect 'liftA2' to inline into 'f1'. We test this by
|
|
4 | +-- grepping for occurrences of the 'Applicative' dictionary.
|
|
5 | +module RWST where
|
|
6 | + |
|
7 | +import Data.Functor.Identity
|
|
8 | +import Control.Applicative
|
|
9 | +import Control.Monad
|
|
10 | + |
|
11 | +newtype RWST r w s m a = RWST { runRWST :: r -> s -> m (w, s, a) }
|
|
12 | + |
|
13 | +instance Functor m => Functor (RWST r w s m) where
|
|
14 | + fmap f (RWST m) = RWST (\r s -> fmap (\ ~(w,s',x) -> (w,s',f x)) (m r s))
|
|
15 | + |
|
16 | +instance (Monoid w, Monad m) => Applicative (RWST r w s m) where
|
|
17 | + pure x = RWST (\_ s -> pure (mempty, s, x))
|
|
18 | + RWST mf <*> RWST mx = RWST (\r s -> do
|
|
19 | + ~(w, s', f) <- mf r s
|
|
20 | + ~(w', s'', x) <- mx r s'
|
|
21 | + pure (w <> w', s'', f x))
|
|
22 | + |
|
23 | +type Pairing m a b = m a -> m b -> m (a, b)
|
|
24 | + |
|
25 | +f1 :: Pairing (RWST r [a] s Identity) a b
|
|
26 | +f1 x y = liftA2 (,) x y
|
|
27 | + |
... | ... | @@ -535,6 +535,7 @@ test('T25160', normal, compile, ['-O -ddump-rules']) |
535 | 535 | test('T25197', [req_th, extra_files(["T25197_TH.hs"]), only_ways(['optasm'])], multimod_compile, ['T25197', '-O2 -v0'])
|
536 | 536 | test('T25389', normal, compile, ['-O -ddump-simpl -dsuppress-uniques -dno-typeable-binds'])
|
537 | 537 | test('T24359a', normal, compile, ['-O -ddump-rules'])
|
538 | +test('T24606', [grep_errmsg(r'fAlternativeRWST')], compile, ['-O -ddump-simpl -dsuppress-uniques -dsuppress-idinfo -dsuppress-coercions -dsuppress-coercion-types'])
|
|
538 | 539 | test('T25713', [grep_errmsg('W:::')], compile, ['-O -ddump-simpl'])
|
539 | 540 | |
540 | 541 | test('T25883', normal, compile_grep_core, [''])
|