Skip to content

Fix pretty printing of ApplicativeDo statements

Kirill Elagin requested to merge kirelagin/ghc:applicative-do-pprint into master

I would be happy to add tests, but I am not quite sure what would be the best strategy here. I guess I could just add a test that compiles a program with renamer output and compares the stdout to what I expect to see, but this will include some unrelated implementation details, such as generated variable names. A better idea might be to generate an expression and call the pretty printer on it as a library. Please, advise.

In essence what happens is this. Given:

{-# LANGUAGE ApplicativeDo #-}

module Test where

q1 :: IO ()
q1 = do
    a <- pure ()
    b <- pure ()
    pure $ pureNothing a
  where
    pureNothing :: a -> ()
    pureNothing _ = ()

q2 :: IO ()
q2 = do
    a <- pure ()
    b <- pure ()
    doNothing a
  where
    doNothing :: a -> IO ()
    doNothing _ = pure ()

Old output:

==================== Renamer ====================
Test.q1 :: IO ()
Test.q1
  = do a_aVI <- pure () | b_aVJ <- pure ()  -- missing parens around parallel bind
       return pureNothing_aVG a_aVI  -- missing parens
  where
      pureNothing_aVG :: a_aVH -> ()
      pureNothing_aVG _ = ()
Test.q2 :: IO ()
Test.q2
  = do join (a_aVM <- pure () | b_aVN <- pure ())  -- bogus join
       doNothing_aVK a_aVM
  where
      doNothing_aVK :: a_aVL -> IO ()
      doNothing_aVK _ = pure ()

New output (hopefully):

==================== Renamer ====================
Test.q1 :: IO ()
Test.q1
  = do (a_aVI <- pure () | b_aVJ <- pure ())
       return (pureNothing_aVG a_aVI)
  where
      pureNothing_aVG :: a_aVH -> ()
      pureNothing_aVG _ = ()
Test.q2 :: IO ()
Test.q2
  = do (a_aVM <- pure () | b_aVN <- pure ())  -- will have `[join]` when debug-ppr
       doNothing_aVK a_aVM
  where
      doNothing_aVK :: a_aVL -> IO ()
      doNothing_aVK _ = pure ()

Originally reported as part of #17768.

Note: WIP for now because no tests and I am actually still waiting for it to compile.

Edited by Kirill Elagin

Merge request reports