RealWorld evaluated?

Out of curiosity, I wondered what would happen if I made up a State# RealWorld token and passed it into an IO action. My intuition was that State# RealWorld is elided in the final program, so none of the IO actions should actually be evaluating it. But when running the below program, I get an error. Why?

{-# LANGUAGE MagicHash #-}
{-# LANGUAGE UnboxedTuples #-}

import Control.Monad.ST
import GHC.Types
import GHC.Prim

main :: IO ()
main = do
  let IO f = putStrLn "asdf"
  let (# _, a #) = f rw
  IO (\s -> (# s, a #))
  where
    rw :: State# RealWorld
    rw = error "real world inspected!"

State# is not a lifted type, so it can’t lazily hide a bomb. Compare:

{-# LANGUAGE MagicHash, UnboxedTuples #-}

import GHC.Prim

main :: IO ()
main = pure ()
 where
  rw :: State# RealWorld
  rw = error "real world inspected!"

The rw binding is strict, as if you had written !rw.

Interesting, thanks! So there’s absolutely no way to construct a State# RealWorld value?

runRW# should be the only way.

Ah no, realWorld# is what I was asking for. Thanks!