[GHC] #13990: Core Lint error on empty case

GHC ghc-devs at haskell.org
Mon Jul 17 19:31:59 UTC 2017


#13990: Core Lint error on empty case
-------------------------------------+-------------------------------------
           Reporter:  mbieleck       |             Owner:  (none)
               Type:  bug            |            Status:  new
           Priority:  normal         |         Milestone:
          Component:  Compiler       |           Version:  8.2.1-rc3
           Keywords:  core-lint      |  Operating System:  Unknown/Multiple
  case                               |
       Architecture:                 |   Type of failure:  Compile-time
  Unknown/Multiple                   |  crash or panic
          Test Case:                 |        Blocked By:
           Blocking:                 |   Related Tickets:
Differential Rev(s):                 |         Wiki Page:
-------------------------------------+-------------------------------------
 This module:

 {{{#!hs
 {-# LANGUAGE EmptyCase #-}
 module Bug where

 data Void

 absurd :: Void -> a
 absurd v = case v of {}

 data Foo = Foo !Void

 absurdFoo :: Foo -> a
 absurdFoo (Foo x) = absurd x
 }}}

 Compiled using `ghc-8.2.0.20170704 -O -dcore-lint Bug.hs`

 Gives the following error:

 {{{
 [1 of 1] Compiling Bug              ( Bug.hs, Bug.o )
 *** Core Lint errors : in result of Simplifier ***
 <no location info>: warning:
     In a case alternative: (Foo x_ap6 :: Void)
     No alternatives for a case scrutinee in head-normal form: x_ap6
 *** Offending Program ***
 absurd :: forall a. Void -> a
 [LclIdX,
  Arity=1,
  Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
          WorkFree=True, Expandable=True,
          Guidance=ALWAYS_IF(arity=1,unsat_ok=True,boring_ok=True)}]
 absurd = \ (@ a_apU) (v_ap5 :: Void) -> case v_ap5 of { }

 absurdFoo :: forall a. Foo -> a
 [LclIdX,
  Arity=1,
  Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
          WorkFree=True, Expandable=True,
          Guidance=ALWAYS_IF(arity=1,unsat_ok=True,boring_ok=True)}]
 absurdFoo
   = \ (@ a_apY) (ds_dUn :: Foo) ->
       case ds_dUn of { Foo x_ap6 -> case x_ap6 of { } }

 -- irrelevant stuff omitted
 }}}

 When I manually inline `absurd` or remove the strictness annotation on
 `Foo`, the error goes away.

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


More information about the ghc-tickets mailing list