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

GHC ghc-devs at haskell.org
Fri Nov 16 15:51:49 UTC 2018


#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=<L,A>] -> GHC.Tuple.() }
 ...
 f2
   = \ (@ a_a1rU) _ [Occ=Dead] (ds_d1tf :: T a_a1rU) ->
       case ds_d1tf of {
         TInt co_a1rX [Dmd=<L,A>] -> GHC.Tuple.();
         TBool ipv_s1tT [Dmd=<B,A>] -> Bug.f4
       }

 Bug.f4
   = Control.Exception.Base.patError
       @ 'GHC.Types.LiftedRep @ () lvl_r1v7
 }}}

-- 
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/15909#comment:1>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler


More information about the ghc-tickets mailing list