[Git][ghc/ghc][wip/expand-do] Regression for #21206 fixed as part of #18324
Apoorv Ingle (@ani)
gitlab at gitlab.haskell.org
Tue Oct 3 13:23:09 UTC 2023
Apoorv Ingle pushed to branch wip/expand-do at Glasgow Haskell Compiler / GHC
Commits:
09c87b21 by Apoorv Ingle at 2023-10-03T08:22:53-05:00
Regression for #21206 fixed as part of #18324
- - - - -
1 changed file:
- + testsuite/tests/typecheck/should_compile/T21206.hs
Changes:
=====================================
testsuite/tests/typecheck/should_compile/T21206.hs
=====================================
@@ -0,0 +1,33 @@
+{-# LANGUAGE QualifiedDo #-}
+module T where
+
+import Prelude hiding (pure, (>>=))
+
+data Free f u a
+ = Pure (u a)
+ | forall x. Free (f u x) (forall u'. u <= u' => u' x -> Free f u' x)
+
+pure :: u a -> Free f u a
+pure = Pure
+(>>=) :: Free f u a -> (forall u'. u <= u' => u' a -> Free f u' a) -> Free f u a
+Pure x >>= k = k x
+
+class f < g where
+ inj :: f u a -> g u a
+
+class u <= u' where
+ inj' :: u a -> u' a
+
+instance u <= u where
+ inj' = id
+
+send :: (f < g) => f u a -> Free g u a
+send op = Free (inj op) Pure
+
+data State s u a where
+ Get :: State s u s
+ Put :: u s -> State s u ()
+
+prog () = T.do
+ x <- send Get
+ Pure x
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/09c87b21bf8edd323916ceb70052620844bf5dc3
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/09c87b21bf8edd323916ceb70052620844bf5dc3
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/20231003/27afa740/attachment-0001.html>
More information about the ghc-commits
mailing list