Skip to content

Trivial thunk gives "undefined reference to stg_ap_0_upd_info"

This error popped up when Alan was coding the solution for #11028 (closed). The error is utterly unrelated to what Alan was working on. Here's a reproducer

{-# OPTIONS_GHC -O -fno-full-laziness #-}
module Main where

foo :: Bool
{-# NOINLINE foo #-}
foo = error "rk"

bar x = let t :: Char
            t = case foo of { True -> 'v'; False -> 'y' }
        in [t]

main = print (bar ())

Just compile that and you get

Foo.o: In function `c1Sm_info':
(.text+0x29a): undefined reference to `stg_ap_0_upd_info'

Why do we get that unresolved symbol? The STG code for bar looks like

Main.bar :: forall t_aup. t_aup -> [GHC.Types.Char]
[GblId, Arity=1, Str=DmdType <L,A>m2, Unf=OtherCon []] =
    \r srt:SRT:[rf :-> Main.foo] [x_s1RR]
        let {
          sat_s1RT [Occ=Once] :: GHC.Types.Char
          [LclId, Str=DmdType] =
              \u srt:SRT:[rf :-> Main.foo] [] Main.foo;
        } in  : [sat_s1RT GHC.Types.[]];

Look at that: an updatable thunk saying sat_s1RT = Main.foo! The error message is terrible, but the problem is a thunk whose only payload is a single variable.

Why does that happen? The Core is

bar =
  \ (@ t_aup) _  -> let t::Char = case foo of wild_00 { }
                    in : @ Char t ([] @ Char)

The case is needed to change foo's type from Bool to Char. The Core-to-STG pass drops the empty case alternatives as useless (rightly), but leaves a bare variable as the RHS, which confuses the code generator.

We should clearly substitute Main.foo for t, either in Core-to-STG, or during code generation.

Why hasn't this happened before now? It is quite hard to provoke, because floating the thunk for t to top level stops it happening. So it only happens if you switch off full laziness (as my test case here does), or if some very delicate inlining happens after the last float-out. The latter is very rare, but it's what happened to Alan.

Edited by Ben Gamari
To upload designs, you'll need to enable LFS and have an admin enable hashed storage. More information