Building comfort-array-0.5.2.3 with an assertion enabled GHC 9.4 results in:
<no location info>: error: ASSERT failed! CallStack (from HasCallStack): assert, called at compiler/GHC/Core/Opt/CprAnal.hs:278:9 in ghc:GHC.Core.Opt.CprAnal
To upload designs, you'll need to enable LFS and have an admin enable hashed storage. More information
Child items
...
Show closed items
Linked items
0
Link issues together to show that they're related or that one is blocking others.
Learn more.
Here's a standalone testcase. To reproduce: ghc -O Shape with a debug compiler. It crashes 9.4 as well as master.
The assertion failure happens during CPR so my earlier suspicion about 23865 was wrong - this is about Core. cc @sgraf812.
{-# LANGUAGE ScopedTypeVariables #-}{-# LANGUAGE RankNTypes #-}{-# LANGUAGE TypeFamilies #-}{-# LANGUAGE GADTs #-}moduleShapewheredataCheckeddataUncheckeddatafamilyResultcheckadatainstanceResultCheckeda=CheckedResultanewtypeinstanceResultUncheckeda=UncheckedResultadataCheckSingletoncheckwhereChecked::CheckSingletonCheckedUnchecked::CheckSingletonUncheckedund::Bool->Boolundx=undxapp::forallcheck.(()->CheckSingletoncheck)->ResultcheckBoolappm=letf::Resultcheck(Bool->Bool)f=casem()ofChecked->CheckedResultundUnchecked->UncheckedResultundincasem()ofChecked->casefofCheckedResultx->CheckedResult(xTrue)Unchecked->UncheckedResultTrue
Take note of the dead case und |> co of CheckedResult x -> rhs expression after we matched m () both for Checked and then for Unchecked. The two coercions co_aFn and co_aFb should be contradictory!
Furthermore, it is an absolute mystery to me where that Case alternative comes from. Certainly it's not part of the original program!
The resilient solution here is to turn the arity assertion into a check and produce top. But I find this kind of code a bit troublesome, dead as it may be.
Here's an even smaller reproducer with the problematic bits and the Note I drafted to explain what goes wrong in CPR:
{-# LANGUAGE TypeFamilies #-}{-# LANGUAGE GADTs #-}{-# LANGUAGE DataKinds #-}moduleT23862wheredatafamilyResult(check::Bool)adatainstanceResultTruea=CheckedResultanewtypeinstanceResultFalsea=UncheckedResultadataCheckSingleton(check::Bool)whereChecked::CheckSingletonTrueUnchecked::CheckSingletonFalseapp::(()->CheckSingletoncheck)->ResultcheckBoolappm=case(m(),m())of(Checked,Unchecked)|CheckedResultx<-UncheckedResult(\_->True)->CheckedResult(xTrue)
Note [Dead code may contain type confusions]~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~In T23862, we have a nested case match that looks like this data CheckSingleton (check :: Bool) where Checked :: CheckSingleton True Unchecked :: CheckSingleton False data family Result (check :: Bool) a data instance Result True a = CheckedResult a newtype instance Result True a = UncheckedResult a case m () of Checked co1 -> case m () of Unchecked co2 -> case ((\_ -> True) |> .. UncheckedResult .. |> sym co2 |> co1) :: Result True (Bool -> Bool) of CheckedResult f -> CheckedResult (f True)Clearly, the innermost case is dead code, because the `Checked` and `Unchecked`cases are apart.However, both constructors introduce mutually contradictory coercions `co1` and`co2` along which GHC generates a type confusion: 1. (\_ -> True) :: Bool -> Bool 2. newtype coercion UncheckedResult (\_ -> True) :: Result False (Bool -> Bool) 3. |> ... sym co1 ... :: Result check (Bool -> Bool) 4. |> ... co2 ... :: Result True (Bool -> Bool)Note that we started with a function, injected into `Result` via a newtypeinstance and then match on it with a datatype instance.We have to handle this case gracefully in `cprAnalAlt`, where for the innermostcase we see a `DataAlt` for `CheckedResult`, yet have a scrutinee type thatabstracts the function `(\_ -> True)` with arity 1.In this case, don't pretend we know anything about the fields of `CheckedResult`!
It was surprising to me that this even type-checks. I suppose the dead code nature is obscured by the need to CSE m ().