[GHC] #15918: mkCastTy sometimes drops insoluble (Type ~ Constraint) coercions
GHC
ghc-devs at haskell.org
Thu Mar 7 10:14:17 UTC 2019
#15918: mkCastTy sometimes drops insoluble (Type ~ Constraint) coercions
-------------------------------------+-------------------------------------
Reporter: Iceland_jack | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone: ⊥
Component: Compiler | Version: 8.6.2
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case: quantified-
| constraints/T15918
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: | https://gitlab.haskell.org/ghc/ghc/merge_requests/489
-------------------------------------+-------------------------------------
Description changed by simonpj:
Old description:
> '''EDIT: See comment:3 for the real cause and comment:17 for the current
> plan.'''
>
> See also:
> * TyCoRep `Note [Respecting definitional equality]` and its supporting
> `Note [Non-trivial definitional equality]`
> * #11715 Constraint vs *
> * #15799
>
> TL;DR: there's a bug in here, that we don't know how to solve. But it's
> not biting us, and once we solve #11715 that may point the way.
>
> ---------------------------
>
> Minimized from
> https://gist.github.com/Icelandjack/683bd4b79027695ffc31632645c9d58b, I
> don't expect `Build []` to kind check but ti shouldn't crash.
>
> {{{#!hs
> {-# Language PolyKinds #-}
> {-# Language TypeFamilies #-}
> {-# Language ConstraintKinds #-}
> {-# Language FlexibleContexts #-}
> {-# Language QuantifiedConstraints #-}
> {-# Language UndecidableInstances #-}
>
> import Data.Kind
>
> class Rev f where
> rev :: f a
>
> instance (forall xx. cls xx => Rev xx) => Rev (Build cls) where
> rev = undefined
>
> data Build :: ((k -> Type) -> Constraint) -> (k -> Type)
>
> uu = rev :: Build [] a
> }}}
>
> gives a panic
>
> {{{
> $ ./ghc-stage2 --interactive -ignore-dot-ghci ~/hs/711_bug.hs
> GHCi, version 8.7.20181029: http://www.haskell.org/ghc/ :? for help
> [1 of 1] Compiling Main ( ~/hs/711_bug.hs, interpreted )
> ghc-stage2: panic! (the 'impossible' happened)
> (GHC version 8.7.20181029 for x86_64-unknown-linux):
> ASSERT failed!
> irred_a1zW :: [(xx_a1zV[sk:3] |> Sym {co_a1zu})]
> Call stack:
> CallStack (from HasCallStack):
> callStackDoc, called at compiler/utils/Outputable.hs:1160:37 in
> ghc:Outputable
> pprPanic, called at compiler/utils/Outputable.hs:1219:5 in
> ghc:Outputable
> assertPprPanic, called at compiler/typecheck/TcType.hs:1826:53 in
> ghc:TcType
>
> Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug
>
> >
> }}}
New description:
'''EDIT: See comment:3 for the real cause and comment:17 for the current
plan.'''
See also:
* TyCoRep `Note [Respecting definitional equality]` and its supporting
`Note [Non-trivial definitional equality]`
* #11715 Constraint vs *
* #15799
* #13650
TL;DR: there's a bug in here, that we don't know how to solve. But it's
not biting us, and once we solve #11715 that may point the way.
---------------------------
Minimized from
https://gist.github.com/Icelandjack/683bd4b79027695ffc31632645c9d58b, I
don't expect `Build []` to kind check but ti shouldn't crash.
{{{#!hs
{-# Language PolyKinds #-}
{-# Language TypeFamilies #-}
{-# Language ConstraintKinds #-}
{-# Language FlexibleContexts #-}
{-# Language QuantifiedConstraints #-}
{-# Language UndecidableInstances #-}
import Data.Kind
class Rev f where
rev :: f a
instance (forall xx. cls xx => Rev xx) => Rev (Build cls) where
rev = undefined
data Build :: ((k -> Type) -> Constraint) -> (k -> Type)
uu = rev :: Build [] a
}}}
gives a panic
{{{
$ ./ghc-stage2 --interactive -ignore-dot-ghci ~/hs/711_bug.hs
GHCi, version 8.7.20181029: http://www.haskell.org/ghc/ :? for help
[1 of 1] Compiling Main ( ~/hs/711_bug.hs, interpreted )
ghc-stage2: panic! (the 'impossible' happened)
(GHC version 8.7.20181029 for x86_64-unknown-linux):
ASSERT failed!
irred_a1zW :: [(xx_a1zV[sk:3] |> Sym {co_a1zu})]
Call stack:
CallStack (from HasCallStack):
callStackDoc, called at compiler/utils/Outputable.hs:1160:37 in
ghc:Outputable
pprPanic, called at compiler/utils/Outputable.hs:1219:5 in
ghc:Outputable
assertPprPanic, called at compiler/typecheck/TcType.hs:1826:53 in
ghc:TcType
Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug
>
}}}
--
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/15918#comment:20>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list