[GHC] #15909: prepareAlts does not take into account equalities which are in scope

#15909: prepareAlts does not take into account equalities which are in scope
-------------------------------------+-------------------------------------
Reporter: mpickering | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone: 8.6.3
Component: Compiler | Version: 8.6.2
Keywords: | Operating System: Unknown/Multiple
Architecture: | Type of failure: None/Unknown
Unknown/Multiple |
Test Case: | Blocked By:
Blocking: | Related Tickets:
Differential Rev(s): | Wiki Page:
-------------------------------------+-------------------------------------
If we consider this program submitted for our consideration by Andres we
see some surprising behaviour.
https://gist.github.com/kosmikus/237946a2335600690208a4a36efef988
{{{
{-# LANGUAGE TypeOperators, GADTs, FlexibleContexts, DataKinds,
RankNTypes, PolyKinds, TypeFamilies, MultiParamTypeClasses,
UndecidableInstances, UndecidableSuperClasses, FlexibleInstances,
ConstraintKinds, TypeApplications, EmptyCase, ScopedTypeVariables,
PartialTypeSignatures, TemplateHaskell #-}
module Partition where
import Data.Coerce
import Data.Kind
import Data.Proxy
data NP (f :: k -> Type) (xs :: [k]) where
Nil :: NP f '[]
(:*) :: f x -> NP f xs -> NP f (x : xs)
infixr 5 :*
strictToPair :: forall f a b . NP f '[a, b] -> (f a, f b)
strictToPair np =
case np of
(fx :* fxs) ->
case (fxs {- :: NP f '[b] -}) of
(fy :* fys) ->
(fx, fy)
}}}
Both pattern matches are exhaustive so we don't need to generate any
failure cases when pattern matching.
Notice in the generated core that we have a match on `Partition.Nil` even
though the match will never
be reached.
{{{
Partition.strictToPair
:: forall k (f :: k -> *) (a :: k) (b :: k).
Partition.NP f '[a, b] -> (f a, f b)
[GblId, Arity=1, Str=m, Unf=OtherCon []]
Partition.strictToPair
= \ (@ k_a1gV)
(@ (f_a1gW :: k_a1gV -> *))
(@ (a_a1gX :: k_a1gV))
(@ (b_a1gY :: k_a1gV))
(np_s1yz [Occ=Once!] :: Partition.NP f_a1gW '[a_a1gX, b_a1gY]) ->
case np_s1yz of
{ Partition.:* @ x_a1h2 @ xs_a1h3 co_a1h4 fx_s1yB [Occ=Once]
fxs_s1yC [Occ=Once!] ->
case fxs_s1yC of {
Partition.Nil _ [Occ=Dead, Dmd=] ->
Partition.strictToPair1 @ k_a1gV @ a_a1gX @ f_a1gW @ b_a1gY;
Partition.:* @ x1_a1h7 @ xs1_a1h8 co1_a1h9 fy_s1yE [Occ=Once]
_ [Occ=Dead] ->
(fx_s1yB
`cast` (

#15909: prepareAlts does not take into account equalities which are in scope
-------------------------------------+-------------------------------------
Reporter: mpickering | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone: 8.6.3
Component: Compiler | Version: 8.6.2
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by RyanGlScott):
Here is a much simpler example which demonstrates the issue:
{{{#!hs
{-# LANGUAGE GADTs #-}
module Bug where
data T a where
TInt :: T Int
TBool :: T Bool
f1 :: T Int -> ()
f1 TInt = ()
f2 :: a ~ Int => T a -> ()
f2 TInt = ()
}}}
{{{
$ /opt/ghc/8.6.2/bin/ghc Bug.hs -O2 -ddump-simpl
[1 of 1] Compiling Bug ( Bug.hs, Bug.o )
==================== Tidy Core ====================
...
f1
= \ (ds_d1tE :: T Int) ->
case ds_d1tE of { TInt co_a1s1 [Dmd=

#15909: prepareAlts does not take into account equalities which are in scope -------------------------------------+------------------------------------- Reporter: mpickering | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.3 Component: Compiler | Version: 8.6.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Reasoning about equalities is the business of the typechecker, and the simplifier doesn't do much. But it does do some things; e.g. it tries to reduce type-family applications. It would be reasonable to try to make it do more; and indeed to support the pattern-match overlap stuff we have an API for the typechecker that can be called externally. I don't know if it's the ''right'' API for this purpose. To make this work we'd have to accumulate the "givens" as we go down. Not too hard. I'd be inclined to do this in a separate pass, NOT the simplifier which has too much else to do. Just possibly the occurrence analyser, though I worry about slowing it down. Another tricky point is that I'd like to be able to prove that every case is exhaustive, and a Lint-checkable property. But if I later remove the second parameter to f2 (it is dead) then it won't be provable anymore. This problem is more basic than fancy equalities. Consider {{{ case x of Red -> e1 DEFAULT -> let v = case x of Red -> e2 Blue -> e3 Green -> e4 in blah }}} we can prune the `Red` branch out of the `case` in the RHS of `v`. But now imagine floating the `v`-binding: {{{ let v = case x of Blue -> e3 Green -> e4 in case x of Red -> e1 DEFAULT -> blah }}} This is actually still correct, but it's not ''obviously'' correct. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15909#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC