QualifiedDo + ApplicativeDo still requires >>=?

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?

Workaround:

class NoBind a where
  (>>=) :: a
instance GHC.TypeError (GHC.Text ">>= is not allowed in a Appl.do block") => NoBind a where
  (>>=) = undefined
1 Like

Does using APPL.pure work?

You might want to use unsatisfiable instead of undefined, not that it matters. Undefined is just a bit of a code smell.

2 Likes

Nope

Main.hs:10:3: error: [GHC-76037]
    Not in scope: ‘Appl.>>=’
    Note: The module ‘Appl’ does not export ‘>>=’.
   |
10 |   x <- Appl.pure 123
   |   ^^^^^^^^^^^^^^^^^^

Separately even if I use pure in the original code, QualifiedDo still looks for Appl.return. Seems like that’s wrong too?

Maybe report this to the GHC issue tracker.

2 Likes

The desugaring uses return on the last line:

Your code uses pure:

Is that the difference?

It’s definitely a bug. I just replicated it myself.

Nope, still repros with return.

Reported in GHC: QualifiedDo + ApplicativeDo still requires >>= and return (#26723) · Issues · Glasgow Haskell Compiler / GHC · GitLab