GHC2021 to GHC2024 - Tips about gotchas?

May I ask for any tips about gotchas with substituting {-# LANGUAGE GHC2024 #-} for {-# LANGUAGE GHC2021 #-}.

I ask because, with Stackage LTS Haskell 24.0 (GHC 9.10.2) now available, I tried to make the move with Stack’s own code base and now a few (about 7%, 14 out of 214) modules refuse to compile. GHC seems to be inferring types differently. I’m trying to work out why.

One example is module Data.Attoparsec.Interpreter (here: https://raw.githubusercontent.com/commercialhaskell/stack/refs/heads/master/src/Data/Attoparsec/Interpreter.hs), which looks pretty pedestrian code to me.

The module compiles with GHC 9.10.2 with:

{-# LANGUAGE Haskell98         #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}

or:

{-# LANGUAGE Haskell2010       #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}

or:

{-# LANGUAGE GHC2021           #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}

but:

{-# LANGUAGE GHC2024           #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}

provokes:

src\Data\Attoparsec\Interpreter.hs:104:32: error: [GHC-83865]
    * Couldn't match type `Text' with `()'
      Expected: Data.Attoparsec.Internal.Types.Parser Text ()
        Actual: P.Parser Text
    * In the second argument of `comment', namely `(P.string "-}")'
      In the expression: comment "{-" (P.string "-}")
      In an equation for `blockComment':
          blockComment = comment "{-" (P.string "-}")
    |
104 |   blockComment = comment "{-" (P.string "-}")
    |                                ^^^^^^^^^^^^^

This has me scratching my head.

2 Likes

I believe GHC2024 enables MonoLocalBinds which might cause this issue.

3 Likes

@AndreasPK, you are a star! It compiles with:

{-# LANGUAGE GHC2024           #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE NoMonoLocalBinds  #-}

The MonoLocalBinds language extension is documented here.

Perhaps a more robust solution would be to give an explicit polymorphic signature to the comment function. MonoLocalBinds is implied by TypeFamilies and GADTs, and if at some point those extensions are enabled for the module, the problem will happen again.

2 Likes

Will do! The practical problem is that before you could ignore the type signatures and GHC was able to work them out. Now you need to work out the type signatures and add them, in order to help the compiler.

Well, it’s not that one-sided. There are examples that use a polymorphic local function without a type signature at several different types and only compile without MonoLocalBinds (like the one you ran into), but there are also examples that only compile with MonoLocalBinds (contrived example below, but I run into this all the time in the real world with effectful)

f :: String -> String
f x = do
    let g z = read x <> z
    -- With MonoLocalBinds, g is inferred to have type `Sum Int -> Sum Int` so this compiles without issues,
    -- but without it, g is generalized to `forall a. (Semigroup a, Read a) => a -> a`
    -- and the type of the second component of the pair is ambiguous
    show (g (5 :: Sum Int), g 5)

It’s not that MonoLocalBinds takes away the reasoning capabilities of the compiler, it just changes what the compiler assumes you mean when you write a local function without a type signature.

2 Likes

Richard Eisenberg has a video defending MonoLocalBinds.

3 Likes

IIUC, a possible way around that is to use PartialTypesignatures (at least while coming up with the signature). The docs say:

Adding a partial type signature f :: _ , (or, more generally, f :: _ => _ ) provides a per-binding way to ask GHC to perform let-generalisation, even though MonoLocalBinds is on.

1 Like

Thanks to everyone for the advice, and to @rae and his former colleagues at Tweag for that video. Stack’s code is now moved on to LANGUAGE GHC2024, without making use of NoMonoLocalBinds. Thanks also to the HLS project; HLS made the step of removing NoMonoLocalBinds far less painful than I had been anticipating.

Removing NoMonoLocalBinds and adding type signatures had the positive side effects of (a) Stack’s own code becomes more expressive (at least, to me) and (b) my realising that some local binds were more polymorphic than they needed to be (and, so, I could tell the compiler that).

My steps were, for each affected module:

  1. Toggle off LANGUAGE NoMonoLocalBinds. HLS used red ink to show me the areas of the code where the problems lay.
  2. Toggle on LANGUAGE NoMonoLocalBinds. Use HLS to hunt down in those general areas local bindings with polymorphic type signatures, and then add those signatures expressly to the code. In most cases, the hunt was straightforward. In only one case (out of 14) it was not.
  3. Consider whether the polymorphic type signatures needed to be as general as they then were.
  4. Consider whether, for the remaining polymorphic type signatures, whether the type variables picked by HLS/GHC output (in step 2) had the most expressive names in the context.
4 Likes