Skip to content

Linear types: double update assertion failure

The following program, taken from simplrun009, causes an assertion failure in master.

{-# LANGUAGE ExistentialQuantification, LambdaCase, LinearTypes #-}

module S where

data Stream = forall s. Stream (Either s s)

f :: x %m -> y %m -> Int
f x y = f x y

step' :: () -> Stream -> Int
step' x (Stream s) =
  (\case
    Left  y -> f x y
    Right y -> f x y) s
ghc-stage2: panic! (the 'impossible' happened)
  (GHC version 9.1.0.20210206:
	ASSERT failed!
  Double update of meta tyvar
    t_aDc[tau:1]
    Indirect t_aDp[tau:0]
  Call stack:
      CallStack (from HasCallStack):
        callStackDoc, called at compiler/GHC/Utils/Panic.hs:181:37 in ghc:GHC.Utils.Panic
        pprPanic, called at compiler/GHC/Utils/Panic.hs:300:5 in ghc:GHC.Utils.Panic
        assertPprPanic, called at compiler/GHC/Tc/Utils/TcMType.hs:1003:60 in ghc:GHC.Tc.Utils.TcMType
        writeMetaTyVarRef, called at compiler/GHC/Tc/Utils/TcMType.hs:962:5 in ghc:GHC.Tc.Utils.TcMType
        writeMetaTyVar, called at compiler/GHC/Tc/Utils/TcMType.hs:2188:10 in ghc:GHC.Tc.Utils.TcMType

Tagging as linear types, because the tyvar t is a multiplicity.

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