According to the QualifiedDo docs, a qualified-do block with -XApplicativeDo enabled should translate to a pure applicative expression:
M.do { (x1 <- u1 | … | xn <- un); M.return e } = (\x1 … xn -> e) `M.fmap` u1 M.<*> … M.<*> un
But this doesn’t seem to be working for a module that intentionally doesn’t provide >>=:
-- Appl.hs
module Appl (
(Prelude.<*>),
(Prelude.>>),
Prelude.pure,
Prelude.return,
Prelude.fmap,
) where
-- Main.hs
{-# LANGUAGE QualifiedDo #-}
{-# LANGUAGE ApplicativeDo #-}
import Appl qualified
main = foo >>= print
foo :: IO Int
foo = Appl.do
x <- pure 123
pure x
$ runghc Main.hs
Main.hs:10:3: error: [GHC-76037]
Not in scope: ‘Appl.>>=’
Note: The module ‘Appl’ does not export ‘>>=’.
|
10 | x <- pure 123
| ^^^^^^^^^^^^^
Is this a compiler bug?